git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@115317 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.1 |
|
5 |
-Date: 2016-03-07 |
|
4 |
+Version: 2.1.2 |
|
5 |
+Date: 2016-03-27 |
|
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")) |
... | ... |
@@ -29,7 +29,7 @@ oncoSimulSample <- function(Nindiv, |
29 | 29 |
if(length(fp$drv)) { |
30 | 30 |
nd <- (2: round(0.75 * length(fp$drv))) |
31 | 31 |
} else { |
32 |
- nd <- 0 |
|
32 |
+ nd <- 9e6 |
|
33 | 33 |
} |
34 | 34 |
} else { |
35 | 35 |
nd <- (2 : round(0.75 * max(fp))) |
... | ... |
@@ -69,6 +69,12 @@ oncoSimulSample <- function(Nindiv, |
69 | 69 |
## leaving detectionSize and detectionDrivers as they are, produces |
70 | 70 |
## the equivalente of uniform sampling. For last, fix a single number |
71 | 71 |
|
72 |
+ ## detectionDrivers when there are none: had we left it at 0, then |
|
73 |
+ ## when there are no drivers we would stop at the first sampling |
|
74 |
+ ## period. |
|
75 |
+ |
|
76 |
+ if(Nindiv < 1) |
|
77 |
+ stop("Nindiv must be >= 1") |
|
72 | 78 |
if(keepPhylog) |
73 | 79 |
warning(paste("oncoSimulSample does not return the phylogeny", |
74 | 80 |
"for now, so there is little point in storing it.")) |
... | ... |
@@ -277,7 +283,7 @@ samplePop <- function(x, timeSample = "last", typeSample = "whole", |
277 | 283 |
oncoSimulPop <- function(Nindiv, |
278 | 284 |
fp, |
279 | 285 |
model = "Exp", |
280 |
- numPassengers = 30, |
|
286 |
+ numPassengers = 0, |
|
281 | 287 |
mu = 1e-6, |
282 | 288 |
detectionSize = 1e8, |
283 | 289 |
detectionDrivers = 4, |
... | ... |
@@ -308,6 +314,9 @@ oncoSimulPop <- function(Nindiv, |
308 | 314 |
mc.cores = detectCores(), |
309 | 315 |
seed = "auto") { |
310 | 316 |
|
317 |
+ if(Nindiv < 1) |
|
318 |
+ stop("Nindiv must be >= 1") |
|
319 |
+ |
|
311 | 320 |
if(.Platform$OS.type == "windows") { |
312 | 321 |
if(mc.cores != 1) |
313 | 322 |
message("You are running Windows. Setting mc.cores = 1") |
... | ... |
@@ -354,7 +363,7 @@ oncoSimulPop <- function(Nindiv, |
354 | 363 |
|
355 | 364 |
oncoSimulIndiv <- function(fp, |
356 | 365 |
model = "Exp", |
357 |
- numPassengers = 30, |
|
366 |
+ numPassengers = 0, |
|
358 | 367 |
mu = 1e-6, |
359 | 368 |
detectionSize = 1e8, |
360 | 369 |
detectionDrivers = 4, |
... | ... |
@@ -393,6 +402,14 @@ oncoSimulIndiv <- function(fp, |
393 | 402 |
"McFL" = "mcfarlandlog", |
394 | 403 |
stop("No valid value for model") |
395 | 404 |
) |
405 |
+ if(initSize < 1) |
|
406 |
+ stop("initSize < 1") |
|
407 |
+ |
|
408 |
+ if( (K < 1) && (model %in% c("McFL", "McFarlandLog") )) { |
|
409 |
+ stop("Using McFarland's model: K cannot be < 1") |
|
410 |
+ } ## if ( !(model %in% c("McFL", "McFarlandLog") )) { |
|
411 |
+ ## K <- 1 ## K is ONLY used for McFarland; set it to 1, to avoid |
|
412 |
+ ## ## C++ blowing. |
|
396 | 413 |
|
397 | 414 |
if(typeFitness == "exp") { |
398 | 415 |
death <- 1 |
... | ... |
@@ -417,7 +434,7 @@ oncoSimulIndiv <- function(fp, |
417 | 434 |
stop("Unknown model") |
418 | 435 |
} |
419 | 436 |
|
420 |
- if(mu < 0) { |
|
437 |
+ if(any(mu < 0)) { |
|
421 | 438 |
stop("mutation rate (mu) is negative") |
422 | 439 |
} |
423 | 440 |
## We do not test for equality to 0. That might be a weird but |
... | ... |
@@ -502,6 +519,12 @@ oncoSimulIndiv <- function(fp, |
502 | 519 |
silent = !verbosity) |
503 | 520 |
objClass <- "oncosimul" |
504 | 521 |
} else { |
522 |
+ if(numPassengers != 0) |
|
523 |
+ warning(paste("Specifying numPassengers has no effect", |
|
524 |
+ " when using fitnessEffects objects. ", |
|
525 |
+ " The fitnessEffects objects are much more ", |
|
526 |
+ "flexible and you can use, for example,", |
|
527 |
+ "the noIntGenes component for passengers.")) |
|
505 | 528 |
if(is.null(seed)) {## Passing a null creates a random seed |
506 | 529 |
## We use a double, to be able to pass in range > 2^16. |
507 | 530 |
## Do not use 0, as that is our way of signaling to C++ to |
... | ... |
@@ -1541,41 +1564,41 @@ oncoSimul.internal <- function(poset, ## restrict.table, |
1541 | 1564 |
rtC <- convertRestrictTable(restrict.table) |
1542 | 1565 |
|
1543 | 1566 |
return(c( |
1544 |
- BNB_Algo5(rtC, |
|
1545 |
- numDrivers, |
|
1546 |
- numGenes, |
|
1547 |
- typeCBN, |
|
1548 |
- birth, |
|
1549 |
- s, |
|
1550 |
- death, |
|
1551 |
- mu, |
|
1552 |
- initSize, |
|
1553 |
- sampleEvery, |
|
1554 |
- detectionSize, |
|
1555 |
- finalTime, |
|
1556 |
- initSize_species, |
|
1557 |
- initSize_iter, |
|
1558 |
- seed, |
|
1559 |
- verbosity, |
|
1560 |
- speciesFS, |
|
1561 |
- ratioForce, |
|
1562 |
- typeFitness, |
|
1563 |
- max.memory, |
|
1564 |
- as.integer(mutationPropGrowth), |
|
1565 |
- initMutant, |
|
1566 |
- max.wall.time, |
|
1567 |
- keepEvery, |
|
1568 |
- alpha, |
|
1569 |
- sh, |
|
1570 |
- K, |
|
1571 |
- # endTimeEvery, |
|
1572 |
- detectionDrivers, |
|
1573 |
- onlyCancer, |
|
1574 |
- errorHitWallTime, |
|
1575 |
- max.num.tries, |
|
1576 |
- errorHitMaxTries, |
|
1577 |
- minDetectDrvCloneSz, |
|
1578 |
- extraTime |
|
1567 |
+ BNB_Algo5(restrictTable = rtC, |
|
1568 |
+ numDrivers = numDrivers, |
|
1569 |
+ numGenes = numGenes, |
|
1570 |
+ typeCBN_ = typeCBN, |
|
1571 |
+ birthRate = birth, |
|
1572 |
+ s = s, |
|
1573 |
+ death = death, |
|
1574 |
+ mu = mu, |
|
1575 |
+ initSize = initSize, |
|
1576 |
+ sampleEvery = sampleEvery, |
|
1577 |
+ detectionSize = detectionSize, |
|
1578 |
+ finalTime = finalTime, |
|
1579 |
+ initSp = initSize_species, |
|
1580 |
+ initIt = initSize_iter, |
|
1581 |
+ seed = seed, |
|
1582 |
+ verbosity = verbosity, |
|
1583 |
+ speciesFS = speciesFS, |
|
1584 |
+ ratioForce = ratioForce, |
|
1585 |
+ typeFitness_= typeFitness, |
|
1586 |
+ maxram = max.memory, |
|
1587 |
+ mutationPropGrowth = as.integer(mutationPropGrowth), |
|
1588 |
+ initMutant = initMutant, |
|
1589 |
+ maxWallTime = max.wall.time, |
|
1590 |
+ keepEvery = keepEvery, |
|
1591 |
+ alpha = alpha, |
|
1592 |
+ sh = sh, |
|
1593 |
+ K = K, |
|
1594 |
+ # end = TimeEvery# , |
|
1595 |
+ detectionDrivers = detectionDrivers, |
|
1596 |
+ onlyCancer = onlyCancer, |
|
1597 |
+ errorHitWallTime = errorHitWallTime, |
|
1598 |
+ maxNumTries = max.num.tries, |
|
1599 |
+ errorHitMaxTries = errorHitMaxTries, |
|
1600 |
+ minDetectDrvCloneSz = minDetectDrvCloneSz, |
|
1601 |
+ extraTime = extraTime |
|
1579 | 1602 |
), |
1580 | 1603 |
NumDrivers = numDrivers |
1581 | 1604 |
)) |
... | ... |
@@ -2,19 +2,18 @@ |
2 | 2 |
# Generator token: 10BE3573-1514-4C36-9D1C-5A225CD40393 |
3 | 3 |
|
4 | 4 |
nr_BNB_Algo5 <- function(rFE, mu, death, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant_, maxWallTime, keepEvery, alpha, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime, keepPhylog) { |
5 |
- .Call('C_OncoSimulR_nr_BNB_Algo5', PACKAGE = 'OncoSimulR', rFE, mu, death, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant_, maxWallTime, keepEvery, alpha, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime, keepPhylog) |
|
5 |
+ .Call('OncoSimulR_nr_BNB_Algo5', PACKAGE = 'OncoSimulR', rFE, mu, death, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant_, maxWallTime, keepEvery, alpha, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime, keepPhylog) |
|
6 | 6 |
} |
7 | 7 |
|
8 | 8 |
BNB_Algo5 <- function(restrictTable, numDrivers, numGenes, typeCBN_, birthRate, s, death, mu, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant, maxWallTime, keepEvery, alpha, sh, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime) { |
9 |
- .Call('C_OncoSimulR_BNB_Algo5', PACKAGE = 'OncoSimulR', restrictTable, numDrivers, numGenes, typeCBN_, birthRate, s, death, mu, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant, maxWallTime, keepEvery, alpha, sh, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime) |
|
9 |
+ .Call('OncoSimulR_BNB_Algo5', PACKAGE = 'OncoSimulR', restrictTable, numDrivers, numGenes, typeCBN_, birthRate, s, death, mu, initSize, sampleEvery, detectionSize, finalTime, initSp, initIt, seed, verbosity, speciesFS, ratioForce, typeFitness_, maxram, mutationPropGrowth, initMutant, maxWallTime, keepEvery, alpha, sh, K, detectionDrivers, onlyCancer, errorHitWallTime, maxNumTries, errorHitMaxTries, minDetectDrvCloneSz, extraTime) |
|
10 | 10 |
} |
11 | 11 |
|
12 |
-## No longer used (or at least not now) |
|
13 | 12 |
## readFitnessEffects <- function(rFE, echo) { |
14 |
-## invisible(.Call('C_OncoSimulR_readFitnessEffects', PACKAGE = 'OncoSimulR', rFE, echo)) |
|
13 |
+## invisible(.Call('OncoSimulR_readFitnessEffects', PACKAGE = 'OncoSimulR', rFE, echo)) |
|
15 | 14 |
## } |
16 | 15 |
|
17 | 16 |
evalRGenotype <- function(rG, rFE, verbose, prodNeg) { |
18 |
- .Call('C_OncoSimulR_evalRGenotype', PACKAGE = 'OncoSimulR', rG, rFE, verbose, prodNeg) |
|
17 |
+ .Call('OncoSimulR_evalRGenotype', PACKAGE = 'OncoSimulR', rG, rFE, verbose, prodNeg) |
|
19 | 18 |
} |
20 | 19 |
|
... | ... |
@@ -32,14 +32,33 @@ |
32 | 32 |
|
33 | 33 |
|
34 | 34 |
check.gm <- function(gm) { |
35 |
- ## Yes, Root: we want no ambiguities |
|
36 |
- if(gm[1] != "Root") |
|
37 |
- stop("First value of a module table must be Root") |
|
38 |
- if(names(gm)[1] != "Root") |
|
39 |
- stop("First name of a module table must be Root") |
|
35 |
+ ## Yes, Root: we want no ambiguities. |
|
36 |
+ |
|
37 |
+ ## Actually, that sucks. So we do not require it, but check for |
|
38 |
+ ## consistency. |
|
39 |
+ |
|
40 |
+ if(any(gm == "Root") && (gm[1] != "Root") ) |
|
41 |
+ stop("If Root is in the module table, it must be the first") |
|
42 |
+ |
|
43 |
+ if(any(names(gm) == "Root") && (names(gm)[1] != "Root") ) |
|
44 |
+ stop("If the name Root is in the module table, it must be the first") |
|
45 |
+ |
|
46 |
+ if( (names(gm)[1] == "Root") && (gm[1] != "Root") ) |
|
47 |
+ stop("The name Root is in the module table, but is not of Root") |
|
48 |
+ |
|
49 |
+ if( (gm[1] == "Root") && (names(gm)[1] != "Root") ) |
|
50 |
+ stop("Root is in the module table, but with a different name") |
|
51 |
+ |
|
52 |
+ ## if(gm[1] != "Root") |
|
53 |
+ ## stop("First value of a module table must be Root") |
|
54 |
+ ## if(names(gm)[1] != "Root") |
|
55 |
+ ## stop("First name of a module table must be Root") |
|
40 | 56 |
if(length(unique(names(gm))) != length(gm)) |
41 | 57 |
stop("Number of unique module names different from length of vector") |
42 |
- |
|
58 |
+ |
|
59 |
+ if(gm[1] != "Root") |
|
60 |
+ gm <- c("Root" = "Root", gm) |
|
61 |
+ return(gm) |
|
43 | 62 |
} |
44 | 63 |
|
45 | 64 |
gtm2 <- function(x) { |
... | ... |
@@ -65,7 +84,8 @@ nice.vector.eo <- function(z, sep, rm.sign = FALSE) { |
65 | 84 |
|
66 | 85 |
gm.to.geneModuleL <- function(gm, one.to.one) { |
67 | 86 |
## the table will be sorted by gene name |
68 |
- check.gm(gm) |
|
87 |
+ gm <- check.gm(gm) |
|
88 |
+ |
|
69 | 89 |
## the named vector with the mapping into the long geneModule df |
70 | 90 |
geneMod <- as.data.frame(rbindlist(lapply(gm, gtm2))) |
71 | 91 |
geneMod$Module <- names(gm)[geneMod[, 2]] ## reverse lookup table |
... | ... |
@@ -724,6 +744,9 @@ fitnessEffectsToIgraph <- function(rT, epistasis, orderEffects) { |
724 | 744 |
df2 <- to.pairs.modules(orderEffects, ">") |
725 | 745 |
} |
726 | 746 |
df <- rbind(df0, df1, df2) |
747 |
+ ## for special case of simple epi effects |
|
748 |
+ if(nrow(df) == 0) return(NULL) |
|
749 |
+ |
|
727 | 750 |
g1 <- graph.data.frame(df) |
728 | 751 |
E(g1)$color <- "black" |
729 | 752 |
E(g1)$color[E(g1)$typeDep == "SM"] <- "blue" |
... | ... |
@@ -21,26 +21,26 @@ |
21 | 21 |
|
22 | 22 |
|
23 | 23 |
|
24 |
-#plot.stream makes a "stream plot" where each y series is plotted |
|
25 |
-#as stacked filled polygons on alternating sides of a baseline. |
|
26 |
-# |
|
27 |
-#Arguments include: |
|
28 |
-#'x' - a vector of values |
|
29 |
-#'y' - a matrix of data series (columns) corresponding to x |
|
30 |
-#'order.method' = c("as.is", "max", "first") |
|
31 |
-# "as.is" - plot in order of y column |
|
32 |
-# "max" - plot in order of when each y series reaches maximum value |
|
33 |
-# "first" - plot in order of when each y series first value > 0 |
|
34 |
-#'center' - if TRUE, the stacked polygons will be centered so that the middle, |
|
35 |
-#i.e. baseline ("g0"), of the stream is approximately equal to zero. |
|
36 |
-#Centering is done before the addition of random wiggle to the baseline. |
|
37 |
-#'frac.rand' - fraction of the overall data "stream" range used to define the range of |
|
38 |
-#random wiggle (uniform distrubution) to be added to the baseline 'g0' |
|
39 |
-#'spar' - setting for smooth.spline function to make a smoothed version of baseline "g0" |
|
40 |
-#'col' - fill colors for polygons corresponding to y columns (will recycle) |
|
41 |
-#'border' - border colors for polygons corresponding to y columns (will recycle) (see ?polygon for details) |
|
42 |
-#'lwd' - border line width for polygons corresponding to y columns (will recycle) |
|
43 |
-#'...' - other plot arguments |
|
24 |
+## plot.stream makes a "stream plot" where each y series is plotted |
|
25 |
+## as stacked filled polygons on alternating sides of a baseline. |
|
26 |
+ |
|
27 |
+## Arguments include: |
|
28 |
+## 'x' - a vector of values |
|
29 |
+## 'y' - a matrix of data series (columns) corresponding to x |
|
30 |
+## 'order.method' = c("as.is", "max", "first") |
|
31 |
+## "as.is" - plot in order of y column |
|
32 |
+## "max" - plot in order of when each y series reaches maximum value |
|
33 |
+## "first" - plot in order of when each y series first value > 0 |
|
34 |
+## 'center' - if TRUE, the stacked polygons will be centered so that the middle, |
|
35 |
+## i.e. baseline ("g0"), of the stream is approximately equal to zero. |
|
36 |
+## Centering is done before the addition of random wiggle to the baseline. |
|
37 |
+## 'frac.rand' - fraction of the overall data "stream" range used to define the range of |
|
38 |
+## random wiggle (uniform distrubution) to be added to the baseline 'g0' |
|
39 |
+## 'spar' - setting for smooth.spline function to make a smoothed version of baseline "g0" |
|
40 |
+## 'col' - fill colors for polygons corresponding to y columns (will recycle) |
|
41 |
+## 'border' - border colors for polygons corresponding to y columns (will recycle) (see ?polygon for details) |
|
42 |
+## 'lwd' - border line width for polygons corresponding to y columns (will recycle) |
|
43 |
+## '...' - other plot arguments |
|
44 | 44 |
|
45 | 45 |
plot.stream2 <- function( |
46 | 46 |
x, y, |
... | ... |
@@ -135,20 +135,20 @@ plot.stream2 <- function( |
135 | 135 |
|
136 | 136 |
|
137 | 137 |
|
138 |
-#plot.stacked makes a stacked plot where each y series is plotted on top |
|
139 |
-#of the each other using filled polygons |
|
140 |
-# |
|
141 |
-#Arguments include: |
|
142 |
-#'x' - a vector of values |
|
143 |
-#'y' - a matrix of data series (columns) corresponding to x |
|
144 |
-#'order.method' = c("as.is", "max", "first") |
|
145 |
-# "as.is" - plot in order of y column |
|
146 |
-# "max" - plot in order of when each y series reaches maximum value |
|
147 |
-# "first" - plot in order of when each y series first value > 0 |
|
148 |
-#'col' - fill colors for polygons corresponding to y columns (will recycle) |
|
149 |
-#'border' - border colors for polygons corresponding to y columns (will recycle) (see ?polygon for details) |
|
150 |
-#'lwd' - border line width for polygons corresponding to y columns (will recycle) |
|
151 |
-#'...' - other plot arguments |
|
138 |
+## plot.stacked makes a stacked plot where each y series is plotted on top |
|
139 |
+## of the each other using filled polygons |
|
140 |
+ |
|
141 |
+## Arguments include: |
|
142 |
+## 'x' - a vector of values |
|
143 |
+## 'y' - a matrix of data series (columns) corresponding to x |
|
144 |
+## 'order.method' = c("as.is", "max", "first") |
|
145 |
+## "as.is" - plot in order of y column |
|
146 |
+## "max" - plot in order of when each y series reaches maximum value |
|
147 |
+## "first" - plot in order of when each y series first value > 0 |
|
148 |
+## 'col' - fill colors for polygons corresponding to y columns (will recycle) |
|
149 |
+## 'border' - border colors for polygons corresponding to y columns (will recycle) (see ?polygon for details) |
|
150 |
+## 'lwd' - border line width for polygons corresponding to y columns (will recycle) |
|
151 |
+## '...' - other plot arguments |
|
152 | 152 |
|
153 | 153 |
plot.stacked2 <- function( |
154 | 154 |
x, y, |
... | ... |
@@ -1,3 +1,10 @@ |
1 |
+Changes in version 2.1.2 (2016-03-27): |
|
2 |
+ - Arguments to BNB_Algo5 explicit. |
|
3 |
+ - Example of modules and no epistasis. |
|
4 |
+ - Remove requirement of Root in geneToModule. |
|
5 |
+ - More tests (and reorganized them) |
|
6 |
+ - Miscell. improvements in documentation and vignette. |
|
7 |
+ |
|
1 | 8 |
Changes in version 2.1.1 (2016-03-07): |
2 | 9 |
- Added mutationPropGrowth as argument. |
3 | 10 |
- Stacked area and stream plots (code from Marc Taylor). |
... | ... |
@@ -70,16 +70,23 @@ allFitnessEffects(rT = NULL, epistasis = NULL, orderEffects = NULL, |
70 | 70 |
} |
71 | 71 |
\item{noIntGenes}{ |
72 | 72 |
A numeric vector (optionally named) with the fitness coefficients of genes |
73 |
- (only genes, not modules) that show no interactions. |
|
74 |
-} |
|
75 |
-\item{geneToModule}{ |
|
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}{ |
|
79 |
+ |
|
76 | 80 |
A named character vector that allows to match genes and modules. The |
77 | 81 |
names are the modules, and each of the values is a character vector |
78 | 82 |
with the gene names, separated by a comma, that correspond to a |
79 | 83 |
module. Note that modules cannot share genes. There is no need for |
80 |
- modules to contain more than one gene. If you specify a geneToModule |
|
81 |
- argument, it must necessarily contain "Root". |
|
84 |
+ modules to contain more than one gene. If you specify a geneToModule |
|
85 |
+ argument, and you used a restriction table, the \code{geneToModule} |
|
86 |
+ must necessarily contain, in the first position, "Root" (since the |
|
87 |
+ restriction table contains a node named "Root"). See examples below. |
|
82 | 88 |
} |
89 |
+ |
|
83 | 90 |
|
84 | 91 |
\item{drvNames}{The names of genes that are considered drivers. This is |
85 | 92 |
only used for: a) deciding when to stop the simulations, in case you |
... | ... |
@@ -207,6 +214,19 @@ fea <- allFitnessEffects(rT = p4, epistasis = epist, orderEffects = oe, |
207 | 214 |
noIntGenes = noint, geneToModule = modules) |
208 | 215 |
|
209 | 216 |
plot(fea) |
217 |
+ |
|
218 |
+ |
|
219 |
+## Modules that show, between them, |
|
220 |
+## no epistasis (so multiplicative effects). |
|
221 |
+## We specify the individual terms, but no value for the ":". |
|
222 |
+ |
|
223 |
+fnme <- allFitnessEffects(epistasis = c("A" = 0.1, |
|
224 |
+ "B" = 0.2), |
|
225 |
+ geneToModule = c("A" = "a1, a2", |
|
226 |
+ "B" = "b1")) |
|
227 |
+ |
|
228 |
+evalAllGenotypes(fnme, order = FALSE, addwt = TRUE) |
|
229 |
+ |
|
210 | 230 |
} |
211 | 231 |
|
212 | 232 |
\keyword{ manip } |
... | ... |
@@ -67,11 +67,12 @@ For \code{evalGenotype} either the value of fitness or (if \code{verbose |
67 | 67 |
For \code{evalAllGenotypes} a data frame with two columns, the Genotype |
68 | 68 |
and the Fitness (or Death Rate, if Bozic). The notation for the Genotype |
69 | 69 |
colum is a follows: when order does not matter, a comma "," separates |
70 |
-the identifier of mutated genes. When order matters, a genotype shown as |
|
71 |
-``x > y _ z'' means that a mutation in ``x'' happened before a mutation |
|
72 |
-in ``y''; there is also a mutation in ``z'', but ``z'' is a gene for |
|
73 |
-which order does not matter. In all cases, a "WT" denotes the wild-type |
|
74 |
-(or, actually, the genotype without any mutations). |
|
70 |
+the identifiers of mutated genes. When order matters, a genotype shown |
|
71 |
+as ``x > y _ z'' means that a mutation in ``x'' happened before a |
|
72 |
+mutation in ``y''; there is also a mutation in ``z'' (which could have |
|
73 |
+happened before or after either of ``x'' or ``y''), but ``z'' is a gene |
|
74 |
+for which order does not matter. In all cases, a "WT" denotes the |
|
75 |
+wild-type (or, actually, the genotype without any mutations). |
|
75 | 76 |
|
76 | 77 |
} |
77 | 78 |
\author{ |
... | ... |
@@ -19,7 +19,7 @@ |
19 | 19 |
al., 2012. |
20 | 20 |
} |
21 | 21 |
\usage{ |
22 |
- oncoSimulIndiv(fp, model = "Exp", numPassengers = 30, mu = 1e-6, |
|
22 |
+ oncoSimulIndiv(fp, model = "Exp", numPassengers = 0, mu = 1e-6, |
|
23 | 23 |
detectionSize = 1e8, detectionDrivers = 4, |
24 | 24 |
sampleEvery = ifelse(model \%in\% c("Bozic", "Exp"), 1, |
25 | 25 |
0.025), |
... | ... |
@@ -39,7 +39,7 @@ |
39 | 39 |
initMutant = NULL, |
40 | 40 |
seed = NULL) |
41 | 41 |
|
42 |
-oncoSimulPop(Nindiv, fp, model = "Exp", numPassengers = 30, mu = 1e-6, |
|
42 |
+oncoSimulPop(Nindiv, fp, model = "Exp", numPassengers = 0, mu = 1e-6, |
|
43 | 43 |
detectionSize = 1e8, detectionDrivers = 4, |
44 | 44 |
sampleEvery = ifelse(model \%in\% c("Bozic", "Exp"), 1, |
45 | 45 |
0.025), |
... | ... |
@@ -73,7 +73,7 @@ oncoSimulSample(Nindiv, |
73 | 73 |
if(length(fp$drv)) { |
74 | 74 |
nd <- (2: round(0.75 * length(fp$drv))) |
75 | 75 |
} else { |
76 |
- nd <- 0 |
|
76 |
+ nd <- 9e6 |
|
77 | 77 |
} |
78 | 78 |
} else { |
79 | 79 |
nd <- (2 : round(0.75 * max(fp))) |
... | ... |
@@ -119,18 +119,24 @@ oncoSimulSample(Nindiv, |
119 | 119 |
v.1. Otherwise, a fitnessEffects object (see |
120 | 120 |
\code{\link{allFitnessEffects}}). |
121 | 121 |
|
122 |
- Other arguments below (s, sh) make sense only if you use a poset, as |
|
123 |
- they are included in the fitnessEffects object. |
|
122 |
+ Other arguments below (s, sh, numPassengers) make sense only if you |
|
123 |
+ use a poset, as they are included in the fitnessEffects object. |
|
124 | 124 |
|
125 | 125 |
} |
126 |
+ |
|
126 | 127 |
\item{model}{ |
127 | 128 |
One of "Bozic", "Exp", "McFarlandLog" (the last one can be abbreviated |
128 |
- to "McFL"). |
|
129 |
+ to "McFL"). The default is "Exp". |
|
129 | 130 |
|
130 | 131 |
} |
132 |
+ |
|
131 | 133 |
\item{numPassengers}{ |
134 |
+ |
|
135 |
+ This has no effect if you use the \code{\link{allFitnessEffects}} |
|
136 |
+ specification. |
|
132 | 137 |
|
133 |
- The number of passenger genes.The total number of genes (drivers plus |
|
138 |
+ If you use the specification of v.1., the number of passenger |
|
139 |
+ genes. Note that using v.1 the total number of genes (drivers plus |
|
134 | 140 |
passengers) must be smaller than 64. |
135 | 141 |
|
136 | 142 |
All driver genes should be included in the poset (even if they depend |
... | ... |
@@ -140,25 +146,37 @@ oncoSimulSample(Nindiv, |
140 | 146 |
of passengers). |
141 | 147 |
|
142 | 148 |
} |
149 |
+ |
|
143 | 150 |
\item{mu}{ |
144 | 151 |
Mutation rate. See also \code{mutationPropGrowth}. |
145 | 152 |
|
146 | 153 |
} \item{detectionSize}{ What is the minimal number of cells for cancer |
147 | 154 |
to be detected. For \code{oncoSimulSample} this can be a vector. |
148 | 155 |
|
149 |
-} |
|
150 |
-\item{detectionDrivers}{ |
|
151 |
- The minimal number of drivers present in any clone for cancer to be |
|
152 |
- detected. For \code{oncoSimulSample} this can be a vector. The default |
|
153 |
- in this case is a vector of drivers from a uniform between 2 and 0.75 |
|
154 |
- the total number of drivers |
|
156 |
+} |
|
157 |
+ |
|
158 |
+\item{detectionDrivers}{ The minimal number of drivers (not modules, |
|
159 |
+drivers, whether or not they are from the same module) present in any |
|
160 |
+clone for cancer to be detected. For \code{oncoSimulSample} this can be |
|
161 |
+a vector. |
|
162 |
+ |
|
163 |
+For \code{oncoSimulSample}, if there are drivers (either because you are |
|
164 |
+using a v.1 object or because you are using a fitnessEffects object with |
|
165 |
+a \code{drvNames} component ---see \code{\link{allFitnessEffects}}---) |
|
166 |
+the default is a vector of drivers from a uniform between 2 and 0.75 the |
|
167 |
+total number of drivers. If there are no drivers (because you are using |
|
168 |
+a fitnessEffects object without a \code{drvNames}, either because you |
|
169 |
+specified it explicitly or because all of the genes are in the |
|
170 |
+noIntGenes component) the simulations should not stop based on the |
|
171 |
+number of drivers (and, thus, the default is set to 9e6). |
|
155 | 172 |
|
156 | 173 |
} |
174 |
+ |
|
157 | 175 |
\item{sampleEvery}{ |
158 | 176 |
|
159 | 177 |
How often the whole population is sampled. This is not the same as the |
160 |
- interval between successive samples that keep stored (for that, see |
|
161 |
- \code{keepEvery}). |
|
178 |
+ interval between successive samples that are kept or stored (for that, |
|
179 |
+ see \code{keepEvery}). |
|
162 | 180 |
|
163 | 181 |
For very fast growing clones, you might need to have a small value |
164 | 182 |
here to minimize possible numerical problems (such as huge increase in |
... | ... |
@@ -393,14 +411,22 @@ to be detected. For \code{oncoSimulSample} this can be a vector. |
393 | 411 |
you set it to "auto", then if you are using v.1, the behavior is the |
394 | 412 |
same as if you set it to NULL (a seed will be generated in R and |
395 | 413 |
passed to C++) but if you are using v.2, a random seed will be |
396 |
- produced in C++. %% using the randutils code from M.E.O'Neill. If you |
|
397 |
- need reproducibility, either pass a value or set it to NULL (setting |
|
414 |
+ produced in C++. %% using the randutils code from M.E.O'Neill. |
|
415 |
+ If you need reproducibility, either pass a value or set it to NULL (setting |
|
398 | 416 |
it to NULL will make the C++ seed reproducible if you use the same |
399 | 417 |
seed in R via \code{set.seed}). However, even using the same value of |
400 | 418 |
\code{seed} is unlikely to give the exact same results between |
401 | 419 |
platforms and compilers. Moreover, note that the defaults for |
402 | 420 |
\code{seed} are not the same in \code{oncoSimulIndiv}, |
403 |
- \code{oncoSimulPop} and \code{oncoSimulSample}. } |
|
421 |
+ \code{oncoSimulPop} and \code{oncoSimulSample}. |
|
422 |
+ |
|
423 |
+ When using oncoSimulPop, if you want reproducibility, you might want |
|
424 |
+ to, in addition to setting \code{seed = NULL}, also do |
|
425 |
+ \code{RNGkind("L'Ecuyer-CMRG")} as we use |
|
426 |
+ \code{\link[parallel]{mclapply}}; look at the vignette of |
|
427 |
+ \pkg{parallel}. |
|
428 |
+ |
|
429 |
+} |
|
404 | 430 |
|
405 | 431 |
|
406 | 432 |
|
... | ... |
@@ -440,8 +466,8 @@ to be detected. For \code{oncoSimulSample} this can be a vector. |
440 | 466 |
|
441 | 467 |
|
442 | 468 |
|
443 |
- \code{GenotyesWDistinctOrderEff} provides the information about |
|
444 |
- order effects that is missing from \code{Genotyoes}. When there are |
|
469 |
+ \code{GenotypesWDistinctOrderEff} provides the information about |
|
470 |
+ order effects that is missing from \code{Genotypes}. When there are |
|
445 | 471 |
order effects, the \code{Genotypes} matrix can contain genotypes |
446 | 472 |
that are not distinguishable. Suppose there are two genes, the first |
447 | 473 |
and the second. In the \code{Genotype} output you can get two |
... | ... |
@@ -449,10 +475,18 @@ to be detected. For \code{oncoSimulSample} this can be a vector. |
449 | 475 |
correspond to the two possible orders (first gene mutated first, or |
450 | 476 |
first gene mutated after the |
451 | 477 |
second). \code{GenotypesWDistinctOrderEff} disambiguates this. The |
452 |
- same is done by \code{GenotypeLabels}; this is easier to decode for |
|
478 |
+ same is done by \code{GenotypesLabels}; this is easier to decode for |
|
453 | 479 |
a human (a string of gene labels) but a little bit harder to parse |
454 |
- automatically. |
|
480 |
+ automatically. Note that when you use the default print method for |
|
481 |
+ this object, you get, among others, a two-column display with the |
|
482 |
+ \code{GenotypeLabels} information. When order matters, a genotype |
|
483 |
+ shown as ``x > y _ z'' means that a mutation in ``x'' happened |
|
484 |
+ before a mutation in ``y''; there is also a mutation in ``z'' (which |
|
485 |
+ could have happened before or after either of ``x'' or ``y''), but |
|
486 |
+ ``z'' is a gene for which order does not matter. When order does not |
|
487 |
+ matter, a comma "," separates the identifiers of mutated genes. |
|
455 | 488 |
|
489 |
+ |
|
456 | 490 |
|
457 | 491 |
|
458 | 492 |
} |
... | ... |
@@ -616,7 +650,7 @@ to be detected. For \code{oncoSimulSample} this can be a vector. |
616 | 650 |
data(examplePosets) |
617 | 651 |
p701 <- examplePosets[["p701"]] |
618 | 652 |
|
619 |
-## Bozic Model |
|
653 |
+## Exp Model |
|
620 | 654 |
|
621 | 655 |
b1 <- oncoSimulIndiv(p701) |
622 | 656 |
summary(b1) |
... | ... |
@@ -223,7 +223,13 @@ |
223 | 223 |
clone is not among the non-shown data (i.e., so that we can see when |
224 | 224 |
each clone/driver originates). |
225 | 225 |
|
226 |
- Thining is done to reduce the plot size and to speed up plotting.. |
|
226 |
+ Thinning is done to reduce the plot size and to speed up plotting. |
|
227 |
+ |
|
228 |
+ Note that thinning is carried out before dealing with the plot axis, |
|
229 |
+ so the actual number of points to be plotted could be a lot less (if |
|
230 |
+ you reduce the x-axis considerably) than those returned from the |
|
231 |
+ thinning. (In extreme cases this could lead to crashes when trying |
|
232 |
+ to use stream plots if, say, you end up plotting only three values). |
|
227 | 233 |
|
228 | 234 |
} |
229 | 235 |
\item{thinData.keep}{ |
... | ... |
@@ -161,7 +161,6 @@ inline void driverCounts(int& maxNumDrivers, |
161 | 161 |
// number of present drivers. |
162 | 162 |
|
163 | 163 |
// We used to do count_NumDrivers and then whichDrivers |
164 |
- |
|
165 | 164 |
maxNumDrivers = 0; |
166 | 165 |
int tmpdr = 0; |
167 | 166 |
int driver_indx; |
... | ... |
@@ -175,11 +174,13 @@ inline void driverCounts(int& maxNumDrivers, |
175 | 174 |
} |
176 | 175 |
if(tmpdr > maxNumDrivers) maxNumDrivers = tmpdr; |
177 | 176 |
} |
178 |
- |
|
179 | 177 |
for(size_t i = 0; i < countByDriver.size(); ++i) { |
180 |
- if(countByDriver[i] > 0) presentDrivers.push_back(i + 1); |
|
181 |
- ++totalPresentDrivers; |
|
178 |
+ if(countByDriver[i] > 0) { |
|
179 |
+ presentDrivers.push_back(i + 1); |
|
180 |
+ ++totalPresentDrivers; |
|
181 |
+ } |
|
182 | 182 |
} |
183 |
+ |
|
183 | 184 |
} |
184 | 185 |
|
185 | 186 |
|
... | ... |
@@ -588,9 +589,10 @@ static void nr_sample_all_pop_P(std::vector<int>& sp_to_remove, |
588 | 589 |
#ifdef DEBUGV |
589 | 590 |
Rcpp::Rcout << "\n\n ********* 5.9 ******\n " |
590 | 591 |
<< " Species = " << i |
591 |
- << "\n Genotype = " << genotypeSingleVector(Genotypes[i]) |
|
592 |
- // << "\n sp_id = " << genotypeSingleVector(Genotypes[i]) // sp_id[i] |
|
593 |
- << "\n pre-update popSize = " |
|
592 |
+ << "\n Genotype = "; |
|
593 |
+ print_Genotype(Genotypes[i]); //genotypeSingleVector(Genotypes[i]) |
|
594 |
+ // << "\n sp_id = " << genotypeSingleVector(Genotypes[i]) // sp_id[i] |
|
595 |
+ Rcpp::Rcout << "\n pre-update popSize = " |
|
594 | 596 |
<< popParams[i].popSize |
595 | 597 |
<< "\n time of sample = " << tSample |
596 | 598 |
<< "\n popParams[i].timeLastUpdate = " |
... | ... |
@@ -620,7 +622,8 @@ static void nr_sample_all_pop_P(std::vector<int>& sp_to_remove, |
620 | 622 |
|
621 | 623 |
#ifdef DEBUGV |
622 | 624 |
Rcpp::Rcout << "\n\n Removing species i = " << i |
623 |
- << " with genotype = " << genotypeSingleVector(Genotypes[i]); |
|
625 |
+ << " with genotype = "; |
|
626 |
+ print_Genotype(Genotypes[i]); //genotypeSingleVector(Genotypes[i]); |
|
624 | 627 |
#endif |
625 | 628 |
} |
626 | 629 |
#ifdef DEBUGV |
... | ... |
@@ -1084,8 +1087,9 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1084 | 1087 |
<< " tSample = " << tSample |
1085 | 1088 |
|
1086 | 1089 |
<< "\n\n** Species = " << u_1 |
1087 |
- << "\n genotype = " << Genotypes[u_1] |
|
1088 |
- << "\n popSize = " << popParams[u_1].popSize |
|
1090 |
+ << "\n genotype = "; |
|
1091 |
+ print_Genotype(Genotypes[u_1]); |
|
1092 |
+ Rcpp::Rcout << "\n popSize = " << popParams[u_1].popSize |
|
1089 | 1093 |
<< "\n currentTime = " << currentTime |
1090 | 1094 |
<< "\n popParams[i].nextMutationTime = " |
1091 | 1095 |
<< tmpdouble1 |
... | ... |
@@ -1113,8 +1117,9 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1113 | 1117 |
<< " tSample = " << tSample |
1114 | 1118 |
|
1115 | 1119 |
<< "\n\n** Species = " << u_1 |
1116 |
- << "\n genotype = " << Genotypes[u_1] |
|
1117 |
- << "\n popSize = " << popParams[u_1].popSize |
|
1120 |
+ << "\n genotype = "; |
|
1121 |
+ print_Genotype(Genotypes[u_1]); |
|
1122 |
+ Rcpp::Rcout << "\n popSize = " << popParams[u_1].popSize |
|
1118 | 1123 |
<< "\n currentTime = " << currentTime |
1119 | 1124 |
<< "\n popParams[i].nextMutationTime = " |
1120 | 1125 |
<< tmpdouble1 |
... | ... |
@@ -1125,8 +1130,9 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1125 | 1130 |
|
1126 | 1131 |
|
1127 | 1132 |
<< "\n\n** Species = " << u_2 |
1128 |
- << "\n genotype = " << Genotypes[u_2] |
|
1129 |
- << "\n popSize = " << popParams[u_2].popSize |
|
1133 |
+ << "\n genotype = "; |
|
1134 |
+ print_Genotype(Genotypes[u_2]); |
|
1135 |
+ Rcpp::Rcout << "\n popSize = " << popParams[u_2].popSize |
|
1130 | 1136 |
<< "\n currentTime = " << currentTime |
1131 | 1137 |
<< "\n popParams[i].nextMutationTime = " |
1132 | 1138 |
<< tmpdouble2 |
... | ... |
@@ -1137,7 +1143,7 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1137 | 1143 |
|
1138 | 1144 |
#endif |
1139 | 1145 |
|
1140 |
- } else { // we sampled, so update all |
|
1146 |
+ } else { // we sampled, so update all: i.e. to_update == 3 |
|
1141 | 1147 |
for(size_t i = 0; i < popParams.size(); i++) { |
1142 | 1148 |
tmpdouble1 = ti_nextTime_tmax_2_st(popParams[i], |
1143 | 1149 |
currentTime, |
... | ... |
@@ -1148,8 +1154,9 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1148 | 1154 |
#ifdef DEBUGV |
1149 | 1155 |
Rcpp::Rcout << "\n\n ********* 5.2: call to ti_nextTime ******\n " |
1150 | 1156 |
<< " Species = " << i |
1151 |
- << "\n genotype = " << Genotypes[i] |
|
1152 |
- << "\n popSize = " << popParams[i].popSize |
|
1157 |
+ << "\n genotype = "; |
|
1158 |
+ print_Genotype(Genotypes[i]); |
|
1159 |
+ Rcpp::Rcout << "\n popSize = " << popParams[i].popSize |
|
1153 | 1160 |
<< "\n currentTime = " << currentTime |
1154 | 1161 |
// << "\n popParams[i].nextMutationTime = " |
1155 | 1162 |
// << popParams[i].nextMutationTime |
... | ... |
@@ -1311,6 +1318,7 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1311 | 1318 |
W_f_st(tmpParam); |
1312 | 1319 |
R_f_st(tmpParam); |
1313 | 1320 |
tmpParam.timeLastUpdate = -99999.99999; //mapTimes_updateP does what it should. |
1321 |
+ // as this is a new species |
|
1314 | 1322 |
popParams.push_back(tmpParam); |
1315 | 1323 |
Genotypes.push_back(newGenotype); |
1316 | 1324 |
to_update = 2; |
... | ... |
@@ -1346,20 +1354,27 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1346 | 1354 |
// #endif |
1347 | 1355 |
} else { // A mutation to pre-existing species |
1348 | 1356 |
#ifdef DEBUGW |
1349 |
- if( (currentTime - popParams[sp].timeLastUpdate) <= 0.0) |
|
1350 |
- throw std::out_of_range("currentTime - timeLastUpdate out of range"); |
|
1357 |
+ if( (currentTime - popParams[sp].timeLastUpdate) <= 0.0) { |
|
1358 |
+ DP2(currentTime); |
|
1359 |
+ DP2(sp); |
|
1360 |
+ DP2(popParams[sp].timeLastUpdate); |
|
1361 |
+ print_spP(popParams[sp]); |
|
1362 |
+ throw std::out_of_range("currentTime - timeLastUpdate out of range"); |
|
1363 |
+ } |
|
1351 | 1364 |
#endif |
1352 | 1365 |
|
1353 | 1366 |
// if(verbosity >= 2) { |
1354 | 1367 |
#ifdef DEBUGV |
1355 | 1368 |
Rcpp::Rcout <<"\n Mutated to existing species " << sp |
1356 |
- << " (Genotype = " << genotypeSingleVector(Genotypes[sp]) |
|
1369 |
+ << " (Genotype = "; |
|
1370 |
+ print_Genotype(Genotypes[sp]); |
|
1357 | 1371 |
// << "; sp_id = " << Genotypes[sp].to_ullong() |
1358 |
- << ")" |
|
1372 |
+ Rcpp::Rcout << ")" |
|
1359 | 1373 |
<< "\n from species " << nextMutant |
1360 |
- << " (Genotypes = " << genotypeSingleVector(Genotypes[nextMutant]) |
|
1374 |
+ << " (Genotypes = "; |
|
1375 |
+ print_Genotype(Genotypes[nextMutant]); |
|
1361 | 1376 |
// << "; sp_id = " << Genotypes[sp].to_ullong() |
1362 |
- << ")"; |
|
1377 |
+ Rcpp::Rcout << ")"; |
|
1363 | 1378 |
// } |
1364 | 1379 |
#endif |
1365 | 1380 |
// FIXME00: the if can be removed?? |
... | ... |
@@ -1372,9 +1387,14 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1372 | 1387 |
} else { |
1373 | 1388 |
throw std::range_error("\n popSize == 0 but existing? \n"); |
1374 | 1389 |
} |
1375 |
- |
|
1376 | 1390 |
#ifdef DEBUGW |
1377 |
- popParams[sp].timeLastUpdate = -99999.99999; // to catch errors |
|
1391 |
+ // This is wrong!!! if we set it to -999999, then the time to |
|
1392 |
+ // next mutation will not be properly updated. In fact, the |
|
1393 |
+ // mapTimes map becomes a mess because the former pv in the |
|
1394 |
+ // popParams is not removed so we end up inserting another pair |
|
1395 |
+ // for the same species. |
|
1396 |
+ |
|
1397 |
+ // popParams[sp].timeLastUpdate = -99999.99999; // to catch errors |
|
1378 | 1398 |
#endif |
1379 | 1399 |
//popParams[sp].Flag = true; |
1380 | 1400 |
} |
... | ... |
@@ -1396,8 +1416,7 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects, |
1396 | 1416 |
// DP2(popParams[nextMutant].popSize); |
1397 | 1417 |
// Rcpp::Rcout << "\n done null mutation; after popSize ********" << std::endl; |
1398 | 1418 |
} |
1399 |
- } |
|
1400 |
- else { // *********** We are sampling ********** |
|
1419 |
+ } else { // *********** We are sampling ********** |
|
1401 | 1420 |
to_update = 3; //short_update = false; |
1402 | 1421 |
if(verbosity >= 2) { |
1403 | 1422 |
Rcpp::Rcout <<"\n We are SAMPLING"; |
... | ... |
@@ -1552,7 +1571,9 @@ Rcpp::List nr_BNB_Algo5(Rcpp::List rFE, |
1552 | 1571 |
|
1553 | 1572 |
|
1554 | 1573 |
|
1555 |
- if(K < 1 ) |
|
1574 |
+ if( (K < 1 ) && ( (typeModel == TypeModel::mcfarlandlog) || |
|
1575 |
+ (typeModel == TypeModel::mcfarland) || |
|
1576 |
+ (typeModel == TypeModel::mcfarland0) )) |
|
1556 | 1577 |
throw std::range_error("K < 1."); |
1557 | 1578 |
fitnessEffectsAll fitnessEffects = convertFitnessEffects(rFE); |
1558 | 1579 |
//Used at least twice |
... | ... |
@@ -1434,8 +1434,13 @@ static void innerBNB(const int& numGenes, |
1434 | 1434 |
//#endif |
1435 | 1435 |
} else { // A mutation to pre-existing species |
1436 | 1436 |
#ifdef DEBUGW |
1437 |
- if( (currentTime - popParams[sp].timeLastUpdate) <= 0.0) |
|
1438 |
- throw std::out_of_range("currentTime - timeLastUpdate out of range"); |
|
1437 |
+ if( (currentTime - popParams[sp].timeLastUpdate) <= 0.0) { |
|
1438 |
+ DP2(currentTime); |
|
1439 |
+ DP2(sp); |
|
1440 |
+ DP2(popParams[sp].timeLastUpdate); |
|
1441 |
+ print_spP(popParams[sp]); |
|
1442 |
+ throw std::out_of_range("currentTime - timeLastUpdate out of range"); |
|
1443 |
+ } |
|
1439 | 1444 |
#endif |
1440 | 1445 |
|
1441 | 1446 |
if(verbosity >= 2) { |
... | ... |
@@ -1459,7 +1464,13 @@ static void innerBNB(const int& numGenes, |
1459 | 1464 |
} |
1460 | 1465 |
|
1461 | 1466 |
#ifdef DEBUGW |
1462 |
- popParams[sp].timeLastUpdate = -99999.99999; // to catch errors |
|
1467 |
+ // This is wrong!!! if we set it to -999999, then the time to |
|
1468 |
+ // next mutation will not be properly updated. In fact, the |
|
1469 |
+ // mapTimes map becomes a mess because the former pv in the |
|
1470 |
+ // popParams is not removed so we end up inserting another pair |
|
1471 |
+ // for the same species. |
|
1472 |
+ |
|
1473 |
+ // popParams[sp].timeLastUpdate = -99999.99999; // to catch errors |
|
1463 | 1474 |
#endif |
1464 | 1475 |
//popParams[sp].Flag = true; |
1465 | 1476 |
} |
... | ... |
@@ -7,14 +7,14 @@ |
7 | 7 |
|
8 | 8 |
SEXP OncoSimulR_nr_BNB_Algo5(SEXP rFESEXP, SEXP muSEXP, SEXP deathSEXP, SEXP initSizeSEXP, SEXP sampleEverySEXP, SEXP detectionSizeSEXP, SEXP finalTimeSEXP, SEXP initSpSEXP, SEXP initItSEXP, SEXP seedSEXP, SEXP verbositySEXP, SEXP speciesFSSEXP, SEXP ratioForceSEXP, SEXP typeFitness_SEXP, SEXP maxramSEXP, SEXP mutationPropGrowthSEXP, SEXP initMutant_SEXP, SEXP maxWallTimeSEXP, SEXP keepEverySEXP, SEXP alphaSEXP, SEXP KSEXP, SEXP detectionDriversSEXP, SEXP onlyCancerSEXP, SEXP errorHitWallTimeSEXP, SEXP maxNumTriesSEXP, SEXP errorHitMaxTriesSEXP, SEXP minDetectDrvCloneSzSEXP, SEXP extraTimeSEXP, SEXP keepPhylogSEXP); |
9 | 9 |
SEXP OncoSimulR_BNB_Algo5(SEXP restrictTableSEXP, SEXP numDriversSEXP, SEXP numGenesSEXP, SEXP typeCBN_SEXP, SEXP birthRateSEXP, SEXP sSEXP, SEXP deathSEXP, SEXP muSEXP, SEXP initSizeSEXP, SEXP sampleEverySEXP, SEXP detectionSizeSEXP, SEXP finalTimeSEXP, SEXP initSpSEXP, SEXP initItSEXP, SEXP seedSEXP, SEXP verbositySEXP, SEXP speciesFSSEXP, SEXP ratioForceSEXP, SEXP typeFitness_SEXP, SEXP maxramSEXP, SEXP mutationPropGrowthSEXP, SEXP initMutantSEXP, SEXP maxWallTimeSEXP, SEXP keepEverySEXP, SEXP alphaSEXP, SEXP shSEXP, SEXP KSEXP, SEXP detectionDriversSEXP, SEXP onlyCancerSEXP, SEXP errorHitWallTimeSEXP, SEXP maxNumTriesSEXP, SEXP errorHitMaxTriesSEXP, SEXP minDetectDrvCloneSzSEXP, SEXP extraTimeSEXP); |
10 |
-SEXP OncoSimulR_readFitnessEffects(SEXP rFESEXP, SEXP echoSEXP); |
|
10 |
+// SEXP OncoSimulR_readFitnessEffects(SEXP rFESEXP, SEXP echoSEXP); |
|
11 | 11 |
SEXP OncoSimulR_evalRGenotype(SEXP rGSEXP, SEXP rFESEXP, SEXP verboseSEXP, SEXP prodNegSEXP); |
12 | 12 |
|
13 | 13 |
R_CallMethodDef callMethods[] = { |
14 |
- {"C_OncoSimulR_nr_BNB_Algo5", (DL_FUNC) &OncoSimulR_nr_BNB_Algo5, 29}, |
|
15 |
- {"C_OncoSimulR_BNB_Algo5", (DL_FUNC) &OncoSimulR_BNB_Algo5, 34}, |
|
16 |
- {"C_OncoSimulR_readFitnessEffects", (DL_FUNC) &OncoSimulR_readFitnessEffects, 2}, |
|
17 |
- {"C_OncoSimulR_evalRGenotype", (DL_FUNC) &OncoSimulR_evalRGenotype, 4}, |
|
14 |
+ {"OncoSimulR_nr_BNB_Algo5", (DL_FUNC) &OncoSimulR_nr_BNB_Algo5, 29}, |
|
15 |
+ {"OncoSimulR_BNB_Algo5", (DL_FUNC) &OncoSimulR_BNB_Algo5, 34}, |
|
16 |
+ // {"OncoSimulR_readFitnessEffects", (DL_FUNC) &OncoSimulR_readFitnessEffects, 2}, |
|
17 |
+ {"OncoSimulR_evalRGenotype", (DL_FUNC) &OncoSimulR_evalRGenotype, 4}, |
|
18 | 18 |
{NULL, NULL, 0} |
19 | 19 |
}; |
20 | 20 |
|
... | ... |
@@ -88,17 +88,19 @@ BEGIN_RCPP |
88 | 88 |
return __result; |
89 | 89 |
END_RCPP |
90 | 90 |
} |
91 |
-// readFitnessEffects |
|
92 |
-void readFitnessEffects(Rcpp::List rFE, bool echo); |
|
93 |
-RcppExport SEXP OncoSimulR_readFitnessEffects(SEXP rFESEXP, SEXP echoSEXP) { |
|
94 |
-BEGIN_RCPP |
|
95 |
- Rcpp::RNGScope __rngScope; |
|
96 |
- Rcpp::traits::input_parameter< Rcpp::List >::type rFE(rFESEXP); |
|
97 |
- Rcpp::traits::input_parameter< bool >::type echo(echoSEXP); |
|
98 |
- readFitnessEffects(rFE, echo); |
|
99 |
- return R_NilValue; |
|
100 |
-END_RCPP |
|
101 |
-} |
|
91 |
+ |
|
92 |
+// // readFitnessEffects |
|
93 |
+// void readFitnessEffects(Rcpp::List rFE, bool echo); |
|
94 |
+// RcppExport SEXP OncoSimulR_readFitnessEffects(SEXP rFESEXP, SEXP echoSEXP) { |
|
95 |
+// BEGIN_RCPP |
|
96 |
+// Rcpp::RNGScope __rngScope; |
|
97 |
+// Rcpp::traits::input_parameter< Rcpp::List >::type rFE(rFESEXP); |
|
98 |
+// Rcpp::traits::input_parameter< bool >::type echo(echoSEXP); |
|
99 |
+// readFitnessEffects(rFE, echo); |
|
100 |
+// return R_NilValue; |
|
101 |
+// END_RCPP |
|
102 |
+// } |
|
103 |
+ |
|
102 | 104 |
// evalRGenotype |
103 | 105 |
double evalRGenotype(Rcpp::IntegerVector rG, Rcpp::List rFE, bool verbose, bool prodNeg); |
104 | 106 |
RcppExport SEXP OncoSimulR_evalRGenotype(SEXP rGSEXP, SEXP rFESEXP, SEXP verboseSEXP, SEXP prodNegSEXP) { |
... | ... |
@@ -781,10 +781,11 @@ void updateRatesBeeren(std::vector<spParamsP>& popParams, |
781 | 781 |
|
782 | 782 |
|
783 | 783 |
void mapTimes_updateP(std::multimap<double, int>& mapTimes, |
784 |
- std::vector<spParamsP>& popParams, |
|
785 |
- const int index, |
|
786 |
- const double time) { |
|
784 |
+ std::vector<spParamsP>& popParams, |
|
785 |
+ const int index, |
|
786 |
+ const double time) { |
|
787 | 787 |
// Update the map times <-> indices |
788 |
+ // Recall this is the map of nextMutationTime and index of species |
|
788 | 789 |
// First, remove previous entry, then insert. |
789 | 790 |
// But if we just created the species, nothing to remove from the map. |
790 | 791 |
if(popParams[index].timeLastUpdate > -1) |
... | ... |
@@ -1100,16 +1100,16 @@ vector<int> getGenotypeDrivers(const Genotype& ge, const vector<int>& drv) { |
1100 | 1100 |
} |
1101 | 1101 |
|
1102 | 1102 |
|
1103 |
-// [[Rcpp::export]] |
|
1104 |
-void readFitnessEffects(Rcpp::List rFE, |
|
1105 |
- bool echo) { |
|
1106 |
- // fitnessEffectsAll fitnessEffects; |
|
1107 |
- // convertFitnessEffects(rFE, fitnessEffects); |
|
1108 |
- fitnessEffectsAll fitnessEffects = convertFitnessEffects(rFE); |
|
1109 |
- if(echo) { |
|
1110 |
- printFitnessEffects(fitnessEffects); |
|
1111 |
- } |
|
1112 |
-} |
|
1103 |
+// // [[Rcpp::export]] |
|
1104 |
+// void readFitnessEffects(Rcpp::List rFE, |
|
1105 |
+// bool echo) { |
|
1106 |
+// // fitnessEffectsAll fitnessEffects; |
|
1107 |
+// // convertFitnessEffects(rFE, fitnessEffects); |
|
1108 |
+// fitnessEffectsAll fitnessEffects = convertFitnessEffects(rFE); |
|
1109 |
+// if(echo) { |
|
1110 |
+// printFitnessEffects(fitnessEffects); |
|
1111 |
+// } |
|
1112 |
+// } |
|
1113 | 1113 |
|
1114 | 1114 |
|
1115 | 1115 |
|
1116 | 1116 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,15 @@ |
1 |
+The tests under this directory are not run automatically when running "R |
|
2 |
+CMD check". They can be run by doing "test_dir()". |
|
3 |
+ |
|
4 |
+They are kept separate because they are long running, many are overkills, |
|
5 |
+and in a few it is possible some might fail even when there are no bugs |
|
6 |
+(since we are comparing expected outcomes from a distribution, and we |
|
7 |
+could end up in unlikely cases). |
|
8 |
+ |
|
9 |
+Note that we will rarely want to use something like try_again (available |
|
10 |
+from the github version of testthat) or repeated tries (e.g., |
|
11 |
+http://stackoverflow.com/questions/20770497/how-to-retry-a-statement-on-error) |
|
12 |
+as that could mean the condition is only true, say, 1/3 or 1/2 of the time |
|
13 |
+and that is NOT a proper test for these cases. However, we might want to |
|
14 |
+decrease the size of populations and allow failure in, say, less than 1 in |
|
15 |
+10 or similar. This way, we might run somewhat faster tests. |
0 | 16 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,242 @@ |
1 |
+RNGkind("Mersenne-Twister") |
|
2 |
+cat(date()) |
|
3 |
+test_that("exercising plotClonePhylog", { |
|
4 |
+ data(examplesFitnessEffects) |
|
5 |
+ tmp <- oncoSimulIndiv(examplesFitnessEffects[["o3"]], |
|
6 |
+ model = "McFL", |
|
7 |
+ mu = 5e-5, |
|
8 |
+ detectionSize = 1e8, |
|
9 |
+ detectionDrivers = 3, |
|
10 |
+ sampleEvery = 0.025, |
|
11 |
+ max.num.tries = 10, |
|
12 |
+ keepEvery = 5, |
|
13 |
+ initSize = 2000, |
|
14 |
+ finalTime = 3000, |
|
15 |
+ onlyCancer = FALSE, |
|
16 |
+ keepPhylog = TRUE) |
|
17 |
+ ## Show only those with N > 10 at end |
|
18 |
+ plotClonePhylog(tmp, N = 10) |
|
19 |
+ ## Show only those with N > 1 between times 5 and 1000 |
|
20 |
+ plotClonePhylog(tmp, N = 1, t = c(5, 1000)) |
|
21 |
+ ## Show everything, even if teminal nodes are extinct |
|
22 |
+ plotClonePhylog(tmp, N = 0) |
|
23 |
+ ## Show time when first appeared |
|
24 |
+ plotClonePhylog(tmp, N = 10, timeEvents = TRUE) |
|
25 |
+ ## This can take a few seconds |
|
26 |
+ plotClonePhylog(tmp, N = 10, keepEvents = TRUE) |
|
27 |
+ ## Reaching the fixOverlap code |
|
28 |
+ plotClonePhylog(tmp, N = 0, timeEvents = TRUE) |
|
29 |
+ }) |
|
30 |
+cat(date()) |
|
31 |
+ |
|
32 |
+date() |
|
33 |
+test_that("exercising the fitnessEffects plotting code", { |
|
34 |
+ data(examplesFitnessEffects) |
|
35 |
+ plot(examplesFitnessEffects[["cbn1"]]) |
|
36 |
+ cs <- data.frame(parent = c(rep("Root", 4), "a", "b", "d", "e", "c"), |
|
37 |
+ child = c("a", "b", "d", "e", "c", "c", rep("g", 3)), |
|
38 |
+ s = 0.1, |
|
39 |
+ sh = -0.9, |
|
40 |
+ typeDep = "MN") |
|
41 |
+ cbn1 <- allFitnessEffects(cs) |
|
42 |
+ plot(cbn1) |
|
43 |
+ plot(cbn1, "igraph") |
|
44 |
+ p4 <- data.frame(parent = c(rep("Root", 4), "A", "B", "D", "E", "C", "F"), |
|
45 |
+ child = c("A", "B", "D", "E", "C", "C", "F", "F", "G", "G"), |
|
46 |
+ s = c(0.01, 0.02, 0.03, 0.04, 0.1, 0.1, 0.2, 0.2, 0.3, 0.3), |
|
47 |
+ sh = c(rep(0, 4), c(-.9, -.9), c(-.95, -.95), c(-.99, -.99)), |
|
48 |
+ typeDep = c(rep("--", 4), |
|
49 |
+ "XMPN", "XMPN", "MN", "MN", "SM", "SM")) |
|
50 |
+ fp4m <- allFitnessEffects(p4, |
|
51 |
+ geneToModule = c("Root" = "Root", "A" = "a1", |
|
52 |
+ "B" = "b1, b2", "C" = "c1", |
|
53 |
+ "D" = "d1, d2", "E" = "e1", |
|
54 |
+ "F" = "f1, f2", "G" = "g1")) |
|
55 |
+ plot(fp4m, expandModules = TRUE) |
|
56 |
+ plot(fp4m, "igraph", layout = igraph::layout.reingold.tilford, |
|
57 |
+ expandModules = TRUE) |
|
58 |
+ plot(fp4m, "igraph", layout = igraph::layout.reingold.tilford, |
|
59 |
+ expandModules = TRUE, autofit = TRUE) |
|
60 |
+ plot(fp4m, expandModules = TRUE, autofit = TRUE) |
|
61 |
+ }) |
|
62 |
+date() |
|
63 |
+ |
|
64 |
+ |
|
65 |
+ |
|
66 |
+ |
|
67 |
+date() |
|
68 |
+test_that("stacked, stream, genotypes and some colors", { |
|
69 |
+ data(examplesFitnessEffects) |
|
70 |
+ tmp <- oncoSimulIndiv(examplesFitnessEffects[["o3"]], |
|
71 |
+ model = "McFL", |
|
72 |
+ mu = 5e-5, |
|
73 |
+ detectionSize = 1e8, |
|
74 |
+ detectionDrivers = 3, |
|
75 |
+ sampleEvery = 0.025, |
|
76 |
+ max.num.tries = 10, |
|
77 |
+ keepEvery = 5, |
|
78 |
+ initSize = 2000, |
|
79 |
+ finalTime = 3000, |
|
80 |
+ onlyCancer = FALSE, |
|
81 |
+ keepPhylog = TRUE) |
|
82 |
+ |
|
83 |
+ plot(tmp, type = "stacked", show = "genotypes") |
|
84 |
+ plot(tmp, type = "stream", show = "genotypes") |
|
85 |
+ plot(tmp, type = "line", show = "genotypes") |
|
86 |
+ |
|
87 |
+ plot(tmp, type = "stacked", show = "drivers") |
|
88 |
+ plot(tmp, type = "stream", show = "drivers") |
|
89 |
+ plot(tmp, type = "line", show = "drivers") |
|
90 |
+ |
|
91 |
+ plot(tmp, type = "stacked", order.method = "max") |
|
92 |
+ plot(tmp, type = "stacked", order.method = "first") |
|
93 |
+ |
|
94 |
+ plot(tmp, type = "stream", order.method = "max") |
|
95 |
+ plot(tmp, type = "stream", order.method = "first") |
|
96 |
+ |
|
97 |
+ plot(tmp, type = "stream", stream.center = TRUE) |
|
98 |
+ plot(tmp, type = "stream", stream.center = FALSE) |
|
99 |
+ |
|
100 |
+ plot(tmp, type = "stream", stream.center = TRUE, log = "x") |
|
101 |
+ plot(tmp, type = "stacked", stream.center = TRUE, log = "x") |
|
102 |
+ |
|
103 |
+ plot(tmp, type = "stacked", show = "genotypes", |
|
104 |
+ breakSortColors = "random") |
|
105 |
+ plot(tmp, type = "stream", show = "genotypes", |
|
106 |
+ breakSortColors = "distave") |
|
107 |
+ |
|
108 |
+ plot(tmp, type = "stacked", show = "genotypes", col = rainbow(9)) |
|
109 |
+ plot(tmp, type = "stream", show = "genotypes", col = rainbow(3)) |
|
110 |
+ plot(tmp, type = "line", show = "genotypes", col = rainbow(20)) |
|
111 |
+ |
|
112 |
+}) |
|
113 |
+date() |
|
114 |
+ |
|
115 |
+ |
|
116 |
+ |
|
117 |
+test_that("xlab, ylab, ylim, xlim can be passed", { |
|
118 |
+ data(examplePosets) |
|
119 |
+ p701 <- examplePosets[["p701"]] |
|
120 |
+ b1 <- oncoSimulIndiv(p701) |
|
121 |
+ plot(b1, addtot = TRUE, plotDiversity = TRUE, xlab = "xlab", |
|
122 |
+ ylab = "ylab", ylim = c(-1000, 1000), log = "", |
|
123 |
+ plotDrivers = TRUE, xlim = c(20, 70)) |
|
124 |
+ plot(b1, show = "drivers", type = "stacked", |
|
125 |
+ xlab = "xlab", |
|
126 |
+ ylab = "ylab", ylim = c(-1000, 1000), |
|
127 |
+ xlim = c(20, 70), |
|
128 |
+ plotDrivers = TRUE) |
|
129 |
+ plot(b1, show = "drivers", type = "stream", |
|
130 |
+ addtot = TRUE, xlab = "xlab", |
|
131 |
+ ylab = "ylab", ylim = c(-100, 1000), |
|
132 |
+ xlim = c(20, 70), |
|
133 |
+ plotDrivers = TRUE) |
|
134 |
+ plot(b1, show = "genotypes", |
|
135 |
+ addtot = TRUE, plotDiversity = TRUE, xlab = "xlab", |
|
136 |
+ ylab = "ylab", ylim = c(1, 1000), |
|
137 |
+ xlim = c(20, 70), |
|
138 |
+ plotDrivers = TRUE) |
|
139 |
+ plot(b1, show = "genotypes", type = "stacked", |
|
140 |
+ xlab = "xlab", |
|
141 |
+ ylab = "ylab", ylim = c(-1000, 1000), |
|
142 |
+ xlim = c(20, 70), |
|
143 |
+ plotDrivers = TRUE) |
|
144 |
+ plot(b1, show = "genotypes", type = "stream", |
|
145 |
+ addtot = TRUE, xlab = "xlab", |
|
146 |
+ ylab = "ylab", ylim = c(-100, 1000), |
|
147 |
+ xlim = c(-20, 70), |
|
148 |
+ plotDrivers = TRUE) |
|
149 |
+ sa <- 0.1 |
|
150 |
+ sb <- -0.2 |
|
151 |
+ sab <- 0.25 |
|
152 |
+ sac <- -0.1 |
|
153 |
+ sbc <- 0.25 |
|
154 |
+ sv2 <- allFitnessEffects(epistasis = c("-A : B" = sb, |
|
155 |
+ "A : -B" = sa, |
|
156 |
+ "A : C" = sac, |
|
157 |
+ "A:B" = sab, |
|
158 |
+ "-A:B:C" = sbc), |
|
159 |
+ geneToModule = c( |
|
160 |
+ "Root" = "Root", |
|
161 |
+ "A" = "a1, a2", |
|
162 |
+ "B" = "b", |
|
163 |
+ "C" = "c")) |
|
164 |
+ e1 <- oncoSimulIndiv(sv2, model = "McFL", |
|
165 |
+ mu = 5e-6, |
|
166 |
+ sampleEvery = 0.02, |
|
167 |
+ keepEvery = 1, |
|
168 |
+ initSize = 2000, |
|
169 |
+ finalTime = 3000, |
|
170 |
+ onlyCancer = FALSE) |
|
171 |
+ plot(e1, addtot = TRUE, plotDiversity = TRUE, xlab = "xlab", |
|
172 |
+ ylab = "ylab", ylim = c(1, 1000), |
|
173 |
+ xlim = c(20, 70), |
|
174 |
+ plotDrivers = TRUE) |
|
175 |
+ plot(e1, show = "drivers", type = "stacked", |
|
176 |
+ xlab = "xlab", |
|
177 |
+ ylab = "ylab", ylim = c(-1000, 1000), |
|
178 |
+ xlim = c(20, 70), |
|
179 |
+ plotDrivers = TRUE) |
|
180 |
+ plot(e1, show = "drivers", type = "stream", |
|
181 |
+ addtot = TRUE, xlab = "xlab", |
|
182 |
+ ylab = "ylab", ylim = c(-100, 1000), |
|
183 |
+ xlim = c(20, 70), |
|
184 |
+ plotDrivers = TRUE) |
|
185 |
+ plot(e1, show = "genotypes", |
|
186 |
+ addtot = TRUE, plotDiversity = TRUE, xlab = "xlab", |
|
187 |
+ ylab = "ylab", ylim = c(-1000, 1000), |
|
188 |
+ xlim = c(20, 70), |
|
189 |
+ plotDrivers = TRUE) |
|
190 |
+ plot(e1, show = "genotypes", type = "stacked", |
|
191 |
+ xlab = "xlab", |
|
192 |
+ ylab = "ylab", ylim = c(-1000, 1000), |
|
193 |
+ xlim = c(20, 70), |
|
194 |
+ plotDrivers = TRUE) |
|
195 |
+ plot(e1, show = "genotypes", type = "stream", |
|
196 |
+ addtot = TRUE, xlab = "xlab", |
|
197 |
+ ylab = "ylab", ylim = c(-100, 1000), |
|
198 |
+ xlim = c(20, 70), |
|
199 |
+ plotDrivers = TRUE) |
|
200 |
+}) |
|
201 |
+ |
|
202 |
+ |
|
203 |
+date() |
|
204 |
+test_that("oncosimul v.1 objects and genotype plotting", { |
|
205 |
+ data(examplePosets) |
|
206 |
+ ## An object of class oncosimul |
|
207 |
+ p705 <- examplePosets[["p705"]] |
|
208 |
+ p1 <- oncoSimulIndiv(p705, keepEvery = 1.1) ## if keepEvery is too |
|
209 |
+ ## large, from time to |
|
210 |
+ ## time you end up with |
|
211 |
+ ## less than 4 sample |
|
212 |
+ ## points and the stream |
|
213 |
+ ## plot breaks |
|
214 |
+ |
|
215 |
+ |
|
216 |
+ ## p1 <- oncoSimulIndiv(p705, model = "McFL", |
|
217 |
+ ## mu = 5e-6, |
|
218 |
+ ## sampleEvery = 0.02, |
|
219 |
+ ## keepEvery = 10, |
|
220 |
+ ## initSize = 2000, |
|
221 |
+ ## finalTime = 3000, |
|
222 |
+ ## onlyCancer = FALSE) |
|
223 |
+ class(p1) |
|
224 |
+ plot(p1, type = "stacked", show = "genotypes", thinData = TRUE) |
|
225 |
+ plot(p1, type = "stream", show = "genotypes", thinData = TRUE) |
|
226 |
+ plot(p1, type = "line", show = "genotypes", thinData = TRUE) |
|
227 |
+}) |
|
228 |
+date() |
|
229 |
+ |
|
230 |
+ |
|
231 |
+ |
|
232 |
+ |
|
233 |
+test_that("passing colors", { |
|
234 |
+ data(examplePosets) |
|
235 |
+ ## An object of class oncosimul |
|
236 |
+ p705 <- examplePosets[["p705"]] |
|
237 |
+ p1 <- oncoSimulIndiv(p705) |
|
238 |
+ class(p1) |
|
239 |
+ plot(p1, type = "stacked", show = "genotypes", col = rainbow(8)) |
|
240 |
+ plot(p1, type = "stream", show = "genotypes", col = rainbow(18)) |
|
241 |
+ plot(p1, type = "line", show = "genotypes", col = rainbow(3)) |
|
242 |
+}) |
0 | 243 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,1555 @@ |
1 |
+cat(paste("\n Starting at mutPropGrowth long", date(), "\n")) |
|
2 |
+ |
|
3 |
+## Why this does not really reflect what we want, and why number of clones |
|
4 |
+## is better that capture the idea of "more mutations". NumClones reflects |
|
5 |
+## the creation of a new clone, something that happens whenever there is a |
|
6 |
+## mutation (that does not land you on a pre-existing clone). |
|
7 |
+ |
|
8 |
+###################################################################### |
|
9 |
+###################################################################### |
|
10 |
+ |
|
11 |
+## ## The functions below measure number of mutated positions by summing |
|
12 |
+## ## number of alleles and dividing by pop.size. But only at final time. |
|
13 |
+## ## And large pops of clones with few muts remain and swamp. |
|
14 |
+ |
|
15 |
+## popS <- function(out) unlist(lapply(out, function(x) x$TotalPopSize)) |
|
16 |
+ |
|
17 |
+## muts <- function(out) { |
|
18 |
+## popSize <- popS(out) |
|
19 |
+## gc <- rowSums(OncoSimulR:::geneCounts(out)) |
|
20 |
+## Muts.per.indiv <- na.omit(gc/popSize) |
|
21 |
+## return(list(PopSize = popSize, |
|
22 |
+## Muts = gc, |
|
23 |
+## Muts.per.indiv = Muts.per.indiv, |
|
24 |
+## Muts.per.indiv.no.0 = Muts.per.indiv[gc > 0])) |
|
25 |
+## } |
|
26 |
+ |
|
27 |
+ |
|
28 |
+## This is better, but still you need time to allow accumulation of clones |
|
29 |
+## with many mutations, and those with few remain |
|
30 |
+ |
|
31 |
+mutsPerClone <- function(x, per.pop.mean = TRUE) { |
|
32 |
+ perCl <- function(z) |
|
33 |
+ unlist(lapply(z$GenotypesWDistinctOrderEff, length)) |
|
34 |
+ perCl2 <- function(z) |
|
35 |
+ mean(unlist(lapply(z$GenotypesWDistinctOrderEff, length))) |
|
36 |
+ |
|
37 |
+ if(per.pop.mean) |
|
38 |
+ unlist(lapply(x, function(u) perCl2(u))) |
|
39 |
+ else |
|
40 |
+ lapply(x, function(u) perCl(u)) |
|
41 |
+} |
|
42 |
+ |
|
43 |
+ |
|
44 |
+###################################################################### |
|
45 |
+###################################################################### |
|
46 |
+ |
|
47 |
+ |
|
48 |
+ |
|
49 |
+ |
|
50 |
+RNGkind("L'Ecuyer-CMRG") ## for the mclapplies |
|
51 |
+## If crashes I want to see where: thus output seed. |
|
52 |
+ |
|
53 |
+ |
|
54 |
+ |
|
55 |
+## this tests takes 10 seconds. Moved to long. So this was in the standard |
|
56 |
+## ones. |
|
57 |
+date() |
|
58 |
+test_that("mutPropGrowth diffs with s> 0", { |
|
59 |
+ pseed <- sample(9999999, 1) |
|
60 |
+ set.seed(pseed) |
|
61 |
+ cat("\n mgp1: the seed is", pseed, "\n") |
|
62 |
+ ft <- 4 ## 2.7 |
|
63 |
+ pops <- 100 |
|
64 |
+ lni <- 150 ## 100 |
|
65 |
+ no <- 1e3 ## 5e1 |
|
66 |
+ ni <- c(2, rep(0, lni)) ## 2 ## 4 ## 5 |
|
67 |
+ mu <- 1e-5 ## 1e-6 |
|
68 |
+ names(ni) <- c("a", paste0("n", seq.int(lni))) |
|
69 |
+ ni <- sample(ni) ## scramble |
|
70 |
+ fe <- allFitnessEffects(noIntGenes = ni) |
|
71 |
+ pseed <- sample(9999999, 1) |
|
72 |
+ set.seed(pseed) |
|
73 |
+ cat("\n mpg1a: the seed is", pseed, "\n") |
|
74 |
+ nca <- oncoSimulPop(pops, fe, finalTime = ft, |
|
75 |
+ mu = mu, |
|
76 |
+ mutationPropGrowth = TRUE, |
|
77 |
+ initSize = no, sampleEvery = 0.1, |
|
78 |
+ initMutant = "a", keepEvery = 1, |
|
79 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
80 |
+ pseed <- sample(9999999, 1) |
|
81 |
+ set.seed(pseed) |
|
82 |
+ cat("\n mpg1c: the seed is", pseed, "\n") |
|
83 |
+ nca2 <- oncoSimulPop(pops, fe, finalTime = ft, |
|
84 |
+ mu = mu, |
|
85 |
+ mutationPropGrowth = FALSE, |
|
86 |
+ initSize = no, sampleEvery = 0.1, |
|
87 |
+ initMutant = "a", keepEvery = 1, |
|
88 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
89 |
+ ## summary(nca)[1:20, c(1, 2, 3, 8, 9)] |
|
90 |
+ ## summary(nca2)[1:20, c(1, 2, 3, 8, 9)] |
|
91 |
+ ## I once saw a weird thing |
|
92 |
+ expect_true(var(summary(nca)$NumClones) > 1e-4) |
|
93 |
+ expect_true(var(summary(nca2)$NumClones) > 1e-4) |
|
94 |
+ ## summary(summary(nca)$NumClones) |
|
95 |
+ ## summary(summary(nca2)$NumClones) |
|
96 |
+ ## summary(mutsPerClone(nca)) |
|
97 |
+ ## summary(mutsPerClone(nca2)) |
|
98 |
+ ## 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))) |
|
103 |
+}) |
|
104 |
+cat("\n", date(), "\n") |
|
105 |
+ |
|
106 |
+ |
|
107 |
+ |
|
108 |
+ |
|
109 |
+ |
|
110 |
+ |
|
111 |
+### Now, test mutPropGrowth does not lead to differences when there are no differences in growth. |
|
112 |
+## Same settings as other tests with similar names, but now no fitness, so |
|
113 |
+## no growth. So no effect of mutationPropGrowth. Note that if we carry |
|
114 |
+## out the tests below when there are differences as in previous tests, we |
|
115 |
+## p <<< 1e-6. |
|
116 |
+ |
|
117 |
+## Note that these tests will fail, as they are based on p-values, with |
|
118 |
+## ... well, a frequency given approx. by the p-value. Thus, we do not use |
|
119 |
+## them in the standard tests. But I run them as part of the long tests; |
|
120 |
+## if they fail, run again to make sure it is just that an unlikely event |
|
121 |
+## happened. |
|
122 |
+ |
|
123 |
+ |
|
124 |
+date() |
|
125 |
+test_that("mutPropGrowth no diffs with s = 0", { |
|
126 |
+ pseed <- sample(9999999, 1) |
|
127 |
+ set.seed(pseed) |
|
128 |
+ cat("\n mgp1ND: the seed is", pseed, "\n") |
|
129 |
+ ft <- 4 ## 2.7 |
|
130 |
+ pops <- 200 |
|
131 |
+ lni <- 150 ## 100 |
|
132 |
+ no <- 1e3 ## 5e1 |
|
133 |
+ ni <- c(0, rep(0, lni)) ## 2 ## 4 ## 5 |
|
134 |
+ mu <- 1e-5 ## 1e-6 |
|
135 |
+ names(ni) <- c("a", paste0("n", seq.int(lni))) |
|
136 |
+ ni <- sample(ni) ## scramble |
|
137 |
+ fe <- allFitnessEffects(noIntGenes = ni) |
|
138 |
+ pseed <- sample(9999999, 1) |
|
139 |
+ set.seed(pseed) |
|
140 |
+ cat("\n mpg1NDa: the seed is", pseed, "\n") |
|
141 |
+ nca <- oncoSimulPop(pops, fe, finalTime = ft, |
|
142 |
+ mu = mu, |
|
143 |
+ mutationPropGrowth = TRUE, |
|
144 |
+ initSize = no, sampleEvery = 0.1, |
|
145 |
+ initMutant = "a", keepEvery = 1, |
|
146 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
147 |
+ pseed <- sample(9999999, 1) |
|
148 |
+ set.seed(pseed) |
|
149 |
+ cat("\n mpg1NDc: the seed is", pseed, "\n") |
|
150 |
+ nca2 <- oncoSimulPop(pops, fe, finalTime = ft, |
|
151 |
+ mu = mu, |
|
152 |
+ mutationPropGrowth = FALSE, |
|
153 |
+ initSize = no, sampleEvery = 0.1, |
|
154 |
+ initMutant = "a", keepEvery = 1, |
|
155 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
156 |
+ ## summary(nca)[1:20, c(1, 2, 3, 8, 9)] |
|
157 |
+ ## summary(nca2)[1:20, c(1, 2, 3, 8, 9)] |
|
158 |
+ p.fail <- 1e-3 |
|
159 |
+ expect_true(t.test(sqrt(summary(nca)$NumClones), |
|
160 |
+ sqrt(summary(nca2)$NumClones))$p.value > p.fail) |
|
161 |
+ expect_true(t.test(sqrt(mutsPerClone(nca)), |
|
162 |
+ sqrt(mutsPerClone(nca2)))$p.value > p.fail) |
|
163 |
+ ## I once saw a weird thing |
|
164 |
+ ## expect_true(var(summary(nca)$NumClones) > 1e-4) |
|
165 |
+ ## expect_true(var(summary(nca2)$NumClones) > 1e-4) |
|
166 |
+ ## summary(summary(nca)$NumClones) |
|
167 |
+ ## summary(summary(nca2)$NumClones) |
|
168 |
+ ## summary(mutsPerClone(nca)) |
|
169 |
+ ## summary(mutsPerClone(nca2)) |
|
170 |
+}) |
|
171 |
+cat("\n", date(), "\n") |
|
172 |
+ |
|
173 |
+ |
|
174 |
+ |
|
175 |
+date() |
|
176 |
+test_that("mutPropGrowth no diffs with s = 0, McFL", { |
|
177 |
+ pseed <- sample(9999999, 1) |
|
178 |
+ set.seed(pseed) |
|
179 |
+ cat("\n mcfND1: the seed is", pseed, "\n") |
|
180 |
+ ft <- 3 |
|
181 |
+ pops <- 200 |
|
182 |
+ lni <- 100 |
|
183 |
+ no <- 1e3 ## 5e1 |
|
184 |
+ ni <- c(0, rep(0, lni)) ## 5 |
|
185 |
+ names(ni) <- c("a", paste0("n", seq.int(lni))) |
|
186 |
+ ni <- sample(ni) ## scramble |
|
187 |
+ fe <- allFitnessEffects(noIntGenes = ni) |
|
188 |
+ pseed <- sample(9999999, 1) |
|
189 |
+ set.seed(pseed) |
|
190 |
+ cat("\n mcfND1a: the seed is", pseed, "\n") |
|
191 |
+ nca <- oncoSimulPop(pops, fe, finalTime = ft, |
|
192 |
+ mutationPropGrowth = TRUE, |
|
193 |
+ initSize = no, |
|
194 |
+ initMutant = "a", model = "McFL", |
|
195 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
196 |
+ pseed <- sample(9999999, 1) |
|
197 |
+ set.seed(pseed) |
|
198 |
+ cat("\n mcfND1c: the seed is", pseed, "\n") |
|
199 |
+ nca2 <- oncoSimulPop(pops, fe, finalTime = ft, |
|
200 |
+ mutationPropGrowth = FALSE, |
|
201 |
+ initSize = no, |
|
202 |
+ initMutant = "a", model = "McFL", |
|
203 |
+ onlyCancer = FALSE, seed = NULL, mc.cores = 2) |
|
204 |
+ ## summary(nca)[1:20, c(1, 2, 3, 8, 9)] |
|