... | ... |
@@ -29,7 +29,7 @@ test_that("Exercise plotting and dealing with different matrix input", { |
29 | 29 |
|
30 | 30 |
m88 <- cbind(B = c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
31 | 31 |
suppressWarnings(expect_identical(as.data.frame( |
32 |
- evalAllGenotypes(allFitnessEffects(genotFitness = m88), |
|
32 |
+ evalAllGenotypes(allFitnessEffects(genotFitness = m88, frequencyDependentFitness = FALSE), |
|
33 | 33 |
addwt = TRUE)), |
34 | 34 |
data.frame(Genotype = c("WT", "A", "B", "A, B"), |
35 | 35 |
Fitness = c(1, 3, 2, 5.5), |
... | ... |
@@ -28,12 +28,13 @@ test_that("Exercise plotting and dealing with different matrix input", { |
28 | 28 |
"One column named ''", fixed = TRUE) |
29 | 29 |
|
30 | 30 |
m88 <- cbind(B = c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
31 |
- expect_identical(as.data.frame( |
|
31 |
+ suppressWarnings(expect_identical(as.data.frame( |
|
32 | 32 |
evalAllGenotypes(allFitnessEffects(genotFitness = m88), |
33 | 33 |
addwt = TRUE)), |
34 | 34 |
data.frame(Genotype = c("WT", "A", "B", "A, B"), |
35 | 35 |
Fitness = c(1, 3, 2, 5.5), |
36 | 36 |
stringsAsFactors = FALSE)) |
37 |
+ ) |
|
37 | 38 |
expect_warning(plotFitnessLandscape(m88), |
38 | 39 |
"One column named ''", fixed = TRUE) |
39 | 40 |
|
... | ... |
@@ -45,15 +46,16 @@ test_that("Exercise plotting and dealing with different matrix input", { |
45 | 46 |
|
46 | 47 |
expect_silent(plot(evalAllGenotypes(fe, order = FALSE))) |
47 | 48 |
|
49 |
+ |
|
48 | 50 |
## same as |
49 | 51 |
expect_silent(plotFitnessLandscape(evalAllGenotypes(fe, order = FALSE))) |
50 | 52 |
## more ggrepel |
51 | 53 |
expect_silent(plot(evalAllGenotypes(fe, order = FALSE), use_ggrepel = TRUE)) |
52 | 54 |
|
53 | 55 |
m98 <- cbind(B = c(2, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
54 |
- expect_error(allFitnessEffects(genotFitness = m98), |
|
56 |
+ suppressWarnings(expect_error(allFitnessEffects(genotFitness = m98), |
|
55 | 57 |
"First ncol - 1 entries not in ", |
56 |
- fixed = TRUE) |
|
58 |
+ fixed = TRUE)) |
|
57 | 59 |
}) |
58 | 60 |
|
59 | 61 |
|
... | ... |
@@ -83,6 +85,7 @@ test_that("to_FitnessMatrix stops as it should", { |
83 | 85 |
|
84 | 86 |
|
85 | 87 |
test_that("to_FitnessMatrix can deal with df", { |
88 |
+ suppressWarnings({ |
|
86 | 89 |
m4 <- data.frame(G = c("A, B", "A", "WT", "B"), |
87 | 90 |
Fitness = c(3, 2, 1, 4)) |
88 | 91 |
expect_message(OncoSimulR:::to_Fitness_Matrix(m4, 2000), |
... | ... |
@@ -106,6 +109,7 @@ test_that("to_FitnessMatrix can deal with df", { |
106 | 109 |
expect_message(plotFitnessLandscape(x3)) |
107 | 110 |
expect_message(plotFitnessLandscape(m5)) |
108 | 111 |
expect_message(plotFitnessLandscape(m4)) |
112 |
+ }) |
|
109 | 113 |
}) |
110 | 114 |
|
111 | 115 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+inittime <- Sys.time() |
|
1 | 2 |
## This actually tests much more than plotFitnessLandscape |
2 | 3 |
cat(paste("\n Starting plotFitnessLandscape at", date())) |
3 | 4 |
test_that("Exercise plotting and dealing with different matrix input", { |
... | ... |
@@ -740,3 +741,5 @@ test_that("Some random checks of the fast peaks function", { |
740 | 741 |
} |
741 | 742 |
}) |
742 | 743 |
cat(paste("\n Ending plotFitnessLandscape at", date()), "\n") |
744 |
+cat(paste(" Took ", round(difftime(Sys.time(), inittime, units = "secs"), 2), "\n\n")) |
|
745 |
+rm(inittime) |
... | ... |
@@ -1,3 +1,5 @@ |
1 |
+## This actually tests much more than plotFitnessLandscape |
|
2 |
+cat(paste("\n Starting plotFitnessLandscape at", date())) |
|
1 | 3 |
test_that("Exercise plotting and dealing with different matrix input", { |
2 | 4 |
r1 <- rfitness(4) |
3 | 5 |
expect_silent(plot(r1)) |
... | ... |
@@ -12,15 +14,27 @@ test_that("Exercise plotting and dealing with different matrix input", { |
12 | 14 |
|
13 | 15 |
m6 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), c(1, 2, 3, 5.5)) |
14 | 16 |
expect_message(plotFitnessLandscape(m6), |
15 |
- "Setting/resetting gene names because", fixed = TRUE) |
|
17 |
+ "No column names:", fixed = TRUE) |
|
16 | 18 |
|
19 |
+ ## the next are so ill formed that they should not be accepted |
|
17 | 20 |
m7 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
18 |
- expect_message(plotFitnessLandscape(m7), |
|
19 |
- "Setting/resetting gene names because", fixed = TRUE) |
|
21 |
+ expect_error(plotFitnessLandscape(m7), |
|
22 |
+ "duplicated column names", fixed = TRUE) |
|
20 | 23 |
|
24 |
+ ## zz: why isn't this working? |
|
21 | 25 |
m8 <- cbind(A = c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
22 |
- expect_message(plotFitnessLandscape(m8), |
|
23 |
- "Setting/resetting gene names because", fixed = TRUE) |
|
26 |
+ expect_warning(plotFitnessLandscape(m8), |
|
27 |
+ "One column named ''", fixed = TRUE) |
|
28 |
+ |
|
29 |
+ m88 <- cbind(B = c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
|
30 |
+ expect_identical(as.data.frame( |
|
31 |
+ evalAllGenotypes(allFitnessEffects(genotFitness = m88), |
|
32 |
+ addwt = TRUE)), |
|
33 |
+ data.frame(Genotype = c("WT", "A", "B", "A, B"), |
|
34 |
+ Fitness = c(1, 3, 2, 5.5), |
|
35 |
+ stringsAsFactors = FALSE)) |
|
36 |
+ expect_warning(plotFitnessLandscape(m88), |
|
37 |
+ "One column named ''", fixed = TRUE) |
|
24 | 38 |
|
25 | 39 |
|
26 | 40 |
## Specify fitness with allFitnessEffects, and plot it |
... | ... |
@@ -34,6 +48,11 @@ test_that("Exercise plotting and dealing with different matrix input", { |
34 | 48 |
expect_silent(plotFitnessLandscape(evalAllGenotypes(fe, order = FALSE))) |
35 | 49 |
## more ggrepel |
36 | 50 |
expect_silent(plot(evalAllGenotypes(fe, order = FALSE), use_ggrepel = TRUE)) |
51 |
+ |
|
52 |
+ m98 <- cbind(B = c(2, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
|
53 |
+ expect_error(allFitnessEffects(genotFitness = m98), |
|
54 |
+ "First ncol - 1 entries not in ", |
|
55 |
+ fixed = TRUE) |
|
37 | 56 |
}) |
38 | 57 |
|
39 | 58 |
|
... | ... |
@@ -720,3 +739,4 @@ test_that("Some random checks of the fast peaks function", { |
720 | 739 |
} |
721 | 740 |
} |
722 | 741 |
}) |
742 |
+cat(paste("\n Ending plotFitnessLandscape at", date()), "\n") |
... | ... |
@@ -272,3 +272,451 @@ test_that("internal peak valley functions", { |
272 | 272 |
|
273 | 273 |
|
274 | 274 |
}) |
275 |
+ |
|
276 |
+ |
|
277 |
+## Beware that using peak_valley on only_accessible makes a difference |
|
278 |
+test_that("internal peak valley functions w/wo inaccessible filter", { |
|
279 |
+ ## A is accessible, a peak |
|
280 |
+ ## AB is a peak if only forward. But there is no |
|
281 |
+ ## reciprocal sign epistasis here! |
|
282 |
+ |
|
283 |
+ ## We want peaks in general, not just |
|
284 |
+ ## under assumption of "no back mutation"? |
|
285 |
+ |
|
286 |
+ ## Well, no, that is not obvious with cancer progression models if we |
|
287 |
+ ## do not allow back mutations. |
|
288 |
+ |
|
289 |
+ ## We get a different result when we restrict to accessible |
|
290 |
+ ## because all < 0 in adjacency are turned to NAs. |
|
291 |
+ |
|
292 |
+ ## Thinking in terms of adjacency matrix, AB is not a peak if it has a |
|
293 |
+ ## positive and a negative entry in its column, because the negative |
|
294 |
+ ## entry means there is an ancestor with larger fitness. |
|
295 |
+ ## But see below for why plainly using the adjacency matrix can give bad results. |
|
296 |
+ |
|
297 |
+ ## The next matrices are all fitness matrix. Last column is fitness. |
|
298 |
+ mf1 <- rbind( |
|
299 |
+ c(0, 0, 1), |
|
300 |
+ c(1, 0, 4), |
|
301 |
+ c(0, 1, 2), |
|
302 |
+ c(1, 1, 3) |
|
303 |
+ ) |
|
304 |
+ |
|
305 |
+ plotFitnessLandscape(mf1) |
|
306 |
+ |
|
307 |
+ expect_equal( |
|
308 |
+ OncoSimulR:::peak_valley( |
|
309 |
+ OncoSimulR:::genot_to_adj_mat(mf1))$peak, 2) |
|
310 |
+ |
|
311 |
+ expect_equal( |
|
312 |
+ OncoSimulR:::peak_valley( |
|
313 |
+ OncoSimulR:::filter_inaccessible( |
|
314 |
+ OncoSimulR:::genot_to_adj_mat(mf1), 0))$peak, |
|
315 |
+ c(2, 4)) |
|
316 |
+ |
|
317 |
+ expect_equal( |
|
318 |
+ OncoSimulR:::fast_peaks(mf1, 0), |
|
319 |
+ c(2, 4)) |
|
320 |
+ |
|
321 |
+ |
|
322 |
+ ## reorder the rows of the matrix. Affects fast_peaks, as it should |
|
323 |
+ mf1 <- rbind( |
|
324 |
+ c(1, 0, 4), |
|
325 |
+ c(0, 0, 1), |
|
326 |
+ c(1, 1, 3), |
|
327 |
+ c(0, 1, 2) |
|
328 |
+ ) |
|
329 |
+ |
|
330 |
+ plotFitnessLandscape(mf1) |
|
331 |
+ ## this is not affected, since it uses, by construction, the ordered matrix |
|
332 |
+ expect_equal( |
|
333 |
+ OncoSimulR:::peak_valley( |
|
334 |
+ OncoSimulR:::genot_to_adj_mat(mf1))$peak, 2) |
|
335 |
+ ## ditto |
|
336 |
+ expect_equal( |
|
337 |
+ OncoSimulR:::peak_valley( |
|
338 |
+ OncoSimulR:::filter_inaccessible( |
|
339 |
+ OncoSimulR:::genot_to_adj_mat(mf1), 0))$peak, |
|
340 |
+ c(2, 4)) |
|
341 |
+ expect_equal( |
|
342 |
+ OncoSimulR:::fast_peaks(mf1, 0), |
|
343 |
+ c(1, 3)) |
|
344 |
+ |
|
345 |
+ |
|
346 |
+ |
|
347 |
+ ## filtering by inaccessible also likely gets rid of all |
|
348 |
+ ## peaks in the non-accessible part of the fitness landscape. |
|
349 |
+ ## But of course those cannot be peaks, since they are inaccessible |
|
350 |
+ |
|
351 |
+ mf3 <- rbind( |
|
352 |
+ c(0, 0, 0, 1), |
|
353 |
+ c(1, 0, 0, 2), |
|
354 |
+ c(0, 1, 0, 0.1), |
|
355 |
+ c(0, 0, 1, 0.3), |
|
356 |
+ c(1, 1, 0, 3), |
|
357 |
+ c(1, 0, 1, 4), |
|
358 |
+ c(0, 1, 1, 0.4), |
|
359 |
+ c(1, 1, 1, 0.2) |
|
360 |
+ ) |
|
361 |
+ |
|
362 |
+ ## plotFitnessLandscape(mf3) |
|
363 |
+ ## BC is detected as a peak, the seventh entry |
|
364 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf3))$peak, |
|
365 |
+ c(5, 6, 7)) |
|
366 |
+ |
|
367 |
+ ## recall this gives the columns of the reduced matrix, which are the former |
|
368 |
+ ## 5 and 6 |
|
369 |
+ expect_equal(OncoSimulR:::peak_valley( |
|
370 |
+ OncoSimulR:::filter_inaccessible( |
|
371 |
+ OncoSimulR:::genot_to_adj_mat(mf3), 0))$peak, |
|
372 |
+ c(3, 4)) |
|
373 |
+ |
|
374 |
+ ## correct indices from original matrix |
|
375 |
+ expect_equal( |
|
376 |
+ OncoSimulR:::fast_peaks(mf3, 0), |
|
377 |
+ c(5, 6)) |
|
378 |
+ |
|
379 |
+ ## works under reorder? |
|
380 |
+ expect_equal( |
|
381 |
+ OncoSimulR:::fast_peaks(mf3[c(5, 1, 2, 3, 7, 4, 6), ], 0), |
|
382 |
+ c(1, 7)) |
|
383 |
+ |
|
384 |
+ |
|
385 |
+ |
|
386 |
+ |
|
387 |
+ mf4 <- rbind( |
|
388 |
+ c(0, 0, 0, 1), |
|
389 |
+ c(1, 0, 0, 2), |
|
390 |
+ c(0, 1, 0, 0.1), |
|
391 |
+ c(0, 0, 1, 0.3), |
|
392 |
+ c(1, 1, 0, 3), |
|
393 |
+ c(1, 0, 1, 4), |
|
394 |
+ c(0, 1, 1, 0.4), |
|
395 |
+ c(1, 1, 1, 1.2) |
|
396 |
+ ) |
|
397 |
+ |
|
398 |
+ ## plotFitnessLandscape(mf4) |
|
399 |
+ |
|
400 |
+ ## ABC is not detected as a peak, because it is not. |
|
401 |
+ ## Issue is not its accessibility, but that AC and AB have larger fitness |
|
402 |
+ ## see example with mf5 |
|
403 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf4))$peak, |
|
404 |
+ c(5, 6)) |
|
405 |
+ |
|
406 |
+ ## recall this gives the columns of the reduced matrix, which are the former |
|
407 |
+ ## 5 and 6 |
|
408 |
+ expect_equal(OncoSimulR:::peak_valley( |
|
409 |
+ OncoSimulR:::filter_inaccessible( |
|
410 |
+ OncoSimulR:::genot_to_adj_mat(mf4), 0))$peak, |
|
411 |
+ c(3, 4)) |
|
412 |
+ |
|
413 |
+ expect_equal( |
|
414 |
+ OncoSimulR:::fast_peaks(mf4, 0), |
|
415 |
+ c(5, 6)) |
|
416 |
+ |
|
417 |
+ |
|
418 |
+ ## Now ABC is accessible |
|
419 |
+ mf5 <- rbind( |
|
420 |
+ c(0, 0, 0, 1), |
|
421 |
+ c(1, 0, 0, 2), |
|
422 |
+ c(0, 1, 0, 0.1), |
|
423 |
+ c(0, 0, 1, 0.3), |
|
424 |
+ c(1, 1, 0, 3), |
|
425 |
+ c(1, 0, 1, 4), |
|
426 |
+ c(0, 1, 1, 0.4), |
|
427 |
+ c(1, 1, 1, 3.5) |
|
428 |
+ ) |
|
429 |
+ |
|
430 |
+ ## plotFitnessLandscape(mf5) |
|
431 |
+ ## plotFitnessLandscape(mf5, only_accessible = TRUE) |
|
432 |
+ |
|
433 |
+ ## But only AC is the peak, correctly |
|
434 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf5))$peak, |
|
435 |
+ c(6)) |
|
436 |
+ |
|
437 |
+ ## Now, both AC and ABC are peaks |
|
438 |
+ ## columns 4 and 5 correspond to genotypes 6 and 8 |
|
439 |
+ expect_equal(OncoSimulR:::peak_valley( |
|
440 |
+ OncoSimulR:::filter_inaccessible( |
|
441 |
+ OncoSimulR:::genot_to_adj_mat(mf5), 0))$peak, |
|
442 |
+ c(4, 5)) |
|
443 |
+ |
|
444 |
+ expect_equal( |
|
445 |
+ OncoSimulR:::fast_peaks(mf5, 0), |
|
446 |
+ c(6, 8)) |
|
447 |
+ |
|
448 |
+ ## AC and ABC same max fitness |
|
449 |
+ mf6 <- rbind( |
|
450 |
+ c(0, 0, 0, 1), |
|
451 |
+ c(1, 0, 0, 2), |
|
452 |
+ c(0, 1, 0, 0.1), |
|
453 |
+ c(0, 0, 1, 0.3), |
|
454 |
+ c(1, 1, 0, 3), |
|
455 |
+ c(1, 0, 1, 4), |
|
456 |
+ c(0, 1, 1, 0.4), |
|
457 |
+ c(1, 1, 1, 4) |
|
458 |
+ ) |
|
459 |
+ |
|
460 |
+ ## plotFitnessLandscape(mf6) |
|
461 |
+ ## Both AC and ABC are peaks. Correctly |
|
462 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf6))$peak, |
|
463 |
+ c(6, 8)) |
|
464 |
+ |
|
465 |
+ ## fast peaks should refuse to run |
|
466 |
+ expect_error( |
|
467 |
+ OncoSimulR:::fast_peaks(mf6, 0), |
|
468 |
+ "There could be several connected maxima", |
|
469 |
+ fixed = TRUE) |
|
470 |
+ |
|
471 |
+ |
|
472 |
+ |
|
473 |
+ ## A and AC |
|
474 |
+ mf7 <- rbind( |
|
475 |
+ c(0, 0, 0, 1), |
|
476 |
+ c(1, 0, 0, 4), |
|
477 |
+ c(0, 1, 0, 0.1), |
|
478 |
+ c(0, 0, 1, 0.3), |
|
479 |
+ c(1, 1, 0, 3), |
|
480 |
+ c(1, 0, 1, 4), |
|
481 |
+ c(0, 1, 1, 0.4), |
|
482 |
+ c(1, 1, 1, 3.4) |
|
483 |
+ ) |
|
484 |
+ ## plotFitnessLandscape(mf7) |
|
485 |
+ ## Both A and AC are peaks. Correctly |
|
486 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf7))$peak, |
|
487 |
+ c(2, 6)) |
|
488 |
+ |
|
489 |
+ ## fast peaks should refuse to run |
|
490 |
+ expect_error( |
|
491 |
+ OncoSimulR:::fast_peaks(mf7, 0), |
|
492 |
+ "There could be several connected maxima", |
|
493 |
+ fixed = TRUE) |
|
494 |
+ |
|
495 |
+ |
|
496 |
+ |
|
497 |
+ ## A, AC, ABC same max fitness |
|
498 |
+ mf8 <- rbind( |
|
499 |
+ c(0, 0, 0, 1), |
|
500 |
+ c(1, 0, 0, 4), |
|
501 |
+ c(0, 1, 0, 0.1), |
|
502 |
+ c(0, 0, 1, 0.3), |
|
503 |
+ c(1, 1, 0, 3), |
|
504 |
+ c(1, 0, 1, 4), |
|
505 |
+ c(0, 1, 1, 0.4), |
|
506 |
+ c(1, 1, 1, 4) |
|
507 |
+ ) |
|
508 |
+ ## plotFitnessLandscape(mf8) |
|
509 |
+ ## Both A and AC are peaks. Correctly |
|
510 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf8))$peak, |
|
511 |
+ c(2, 6, 8)) |
|
512 |
+ |
|
513 |
+ |
|
514 |
+ ## fast peaks should refuse to run |
|
515 |
+ expect_error( |
|
516 |
+ OncoSimulR:::fast_peaks(mf8, 0), |
|
517 |
+ "There could be several connected maxima", |
|
518 |
+ fixed = TRUE) |
|
519 |
+ |
|
520 |
+ ## A, AC, AB same max fitness |
|
521 |
+ mf9 <- rbind( |
|
522 |
+ c(0, 0, 0, 1), |
|
523 |
+ c(1, 0, 0, 4), |
|
524 |
+ c(0, 1, 0, 0.1), |
|
525 |
+ c(0, 0, 1, 0.3), |
|
526 |
+ c(1, 1, 0, 4), |
|
527 |
+ c(1, 0, 1, 4), |
|
528 |
+ c(0, 1, 1, 0.4), |
|
529 |
+ c(1, 1, 1, 2.4) |
|
530 |
+ ) |
|
531 |
+ ## plotFitnessLandscape(mf9, use_ggrepel = TRUE) |
|
532 |
+ ## Both A and AC are peaks. Correctly |
|
533 |
+ expect_equal(OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(mf9))$peak, |
|
534 |
+ c(2, 5, 6)) |
|
535 |
+ |
|
536 |
+ |
|
537 |
+ |
|
538 |
+ ## This illustrates that the "filter_inaccessible" is not just "do |
|
539 |
+ ## not take into account inaccessible genotypes" but, properly, do |
|
540 |
+ ## not take into account, do not allow any travelling through |
|
541 |
+ ## inaccessible paths. |
|
542 |
+ |
|
543 |
+ ## Thus, filter_inaccessible is the way to go if we want to exclude |
|
544 |
+ ## backmutation. In no bakcmutation, it is not possible to go from |
|
545 |
+ ## m+1 to m mutations. |
|
546 |
+ |
|
547 |
+ ## It also shows that naively looking at the adjacency matrix can |
|
548 |
+ ## fail. Two reasons: |
|
549 |
+ |
|
550 |
+ ## a) the last row will never have any entries and yet it need not |
|
551 |
+ ## be a peak. |
|
552 |
+ |
|
553 |
+ ## b) simply looking at adjacency matrix is not the correct |
|
554 |
+ ## procedure when some fitnesses can be equal. That is what the |
|
555 |
+ ## function peak_valley works hard to get right :-) |
|
556 |
+ |
|
557 |
+ |
|
558 |
+ cp2 <- structure(c(0, 1, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 0, 0, 0, |
|
559 |
+0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, |
|
560 |
+1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, |
|
561 |
+0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, |
|
562 |
+1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 1, |
|
563 |
+1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 1, |
|
564 |
+1, 1, 1, 1, 0, 1, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, |
|
565 |
+1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 0, 0, |
|
566 |
+0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, |
|
567 |
+0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, |
|
568 |
+0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, |
|
569 |
+1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 0, |
|
570 |
+1, 1, 1, 1, 1, 0, 1, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, |
|
571 |
+0, 1, 0, 0, 0, 0, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, |
|
572 |
+1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, |
|
573 |
+1, 1, 1, 1, 1, 0, 0, 0, 0, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 1, |
|
574 |
+1, 1, 1, 1, 0, 0, 0, 0, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 1, 1, 1, |
|
575 |
+1, 0, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 1, 1, 1, 1, 0, 1, 1, 1, 1, |
|
576 |
+0, 1, 1, 1, 1, 1, 0, 1, 1, 1, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, |
|
577 |
+0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 1, 0, |
|
578 |
+0, 0, 1, 0, 0, 0, 1, 1, 1, 0, 0, 0, 1, 0, 0, 0, 1, 1, 1, 0, 0, |
|
579 |
+0, 1, 1, 1, 0, 0, 0, 1, 1, 1, 0, 1, 0, 0, 0, 1, 1, 1, 0, 0, 0, |
|
580 |
+1, 1, 1, 0, 0, 0, 1, 1, 1, 0, 1, 1, 1, 0, 0, 0, 1, 1, 1, 0, 1, |
|
581 |
+1, 1, 0, 1, 1, 1, 1, 0, 0, 0, 1, 1, 1, 0, 1, 1, 1, 0, 1, 1, 1, |
|
582 |
+1, 0, 1, 1, 1, 1, 1, 0, 1, 1, 1, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, |
|
583 |
+0, 0, 1, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 0, 1, 1, 0, 0, |
|
584 |
+0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 0, 1, 1, 0, 0, 1, 0, 0, 1, 0, 0, |
|
585 |
+1, 1, 0, 1, 0, 0, 1, 1, 0, 1, 1, 0, 1, 0, 1, 0, 0, 1, 0, 0, 1, |
|
586 |
+1, 0, 1, 0, 0, 1, 1, 0, 1, 1, 0, 1, 1, 0, 0, 1, 1, 0, 1, 1, 0, |
|
587 |
+1, 1, 1, 0, 1, 1, 1, 0, 0, 1, 1, 0, 1, 1, 0, 1, 1, 1, 0, 1, 1, |
|
588 |
+1, 1, 0, 1, 1, 1, 1, 1, 0, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, |
|
589 |
+0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 1, 0, |
|
590 |
+1, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 1, 0, 1, 0, 0, 1, 0, 0, |
|
591 |
+1, 0, 1, 0, 1, 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 0, 0, 1, 0, 0, 1, |
|
592 |
+0, 1, 0, 1, 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 0, 1, 0, 1, 0, 1, 1, |
|
593 |
+0, 1, 1, 1, 0, 1, 1, 1, 0, 1, 0, 1, 0, 1, 1, 0, 1, 1, 1, 0, 1, |
|
594 |
+1, 1, 1, 0, 1, 1, 1, 1, 1, 0, 1, 1, 1, 1, 1, 1, 0, 0, 0, 0, 0, |
|
595 |
+0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, |
|
596 |
+0, 1, 1, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 0, 1, 1, 0, 0, 0, |
|
597 |
+1, 0, 0, 1, 0, 1, 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1, 0, 0, 0, 1, |
|
598 |
+0, 0, 1, 0, 1, 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1, 0, 0, 1, 0, 1, |
|
599 |
+1, 0, 1, 1, 1, 0, 1, 1, 1, 1, 0, 0, 1, 0, 1, 1, 0, 1, 1, 1, 0, |
|
600 |
+1, 1, 1, 1, 0, 1, 1, 1, 1, 1, 0, 1, 1, 1, 1, 1, 1, 1, 1, 0.852873407703003, |
|
601 |
+1.51520969989942, 1.09934414414554, 1.08362391548151, 1.06352377058758, |
|
602 |
+0.875558455823467, 1.69351291065104, 2.92492684398312, 1.02057836095586, |
|
603 |
+0.994559647972076, 1.01807462848707, 0.782398502758159, 0.755318352952028, |
|
604 |
+1.81553780643735, 1.7427209966816, 1.00116069406198, 0.790243245268257, |
|
605 |
+3.38168029927183, 1.18573953796889, 1.24679706264807, 0.944183929293486, |
|
606 |
+1.04153712305771, 1.20232261789798, 1.0345783487807, 1.04678440594199, |
|
607 |
+0.993244793867836, 0.97914067773803, 0.79321495112376, 0.868101325153957, |
|
608 |
+0.866235177920767, 4.1155779007473, 3.163209721772, 4.34977195536485, |
|
609 |
+1.09932137400121, 1.08612305022998, 0.916953742980573, 0.850115441923501, |
|
610 |
+1.06277833622263, 0.865087563773651, 0.928169473201598, 0.904902930158639, |
|
611 |
+0.897493717866434, 0.71149600120298, 1.06538015204221, 1.07859259299858, |
|
612 |
+0.858803230350538, 2.25551012930227, 1.09241633274047, 0.870425423271033, |
|
613 |
+2.17687545546796, 0.84459090869647, 4.58149975106353, 3.85245245151455, |
|
614 |
+1.28342034151899, 1.08529050597462, 1.02256835452167, 1.04982916832593, |
|
615 |
+1.0457848642841, 0.90107628754529, 1.08969768294891, 1.05766476796899, |
|
616 |
+0.902394628842996, 0.888348932462492, 1.01037474862489, 0.954093541062801, |
|
617 |
+0.807820459139572, 2.74832174163312, 1.01318977068049, 0.854004033396404, |
|
618 |
+0.842034005421367, 0.800544915243185, 5.31108977064723, 5.31423066433053, |
|
619 |
+1.16539625099584, 0.983449927610599, 0.996320237843515, 0.9794158873742, |
|
620 |
+1.02038748073625, 0.808875731463122, 0.964868528161141, 0.966566509486774, |
|
621 |
+0.860373057266184, 0.81168825662344, 1.19978481918247, 0.98157798351476, |
|
622 |
+0.999463234369357, 0.98711106267367, 0.961995700808845, 4.79391503400402, |
|
623 |
+0.998909701750288, 0.996465768481649, 0.785688019266101, 0.778917380394268, |
|
624 |
+1.17230915723272, 1.19911647477422, 0.961939861987872, 0.981542927739855, |
|
625 |
+0.999822362533057, 1.15236749698624, 0.919688401637553, 0.876733220798505, |
|
626 |
+0.92069327916386, 0.958801043337062, 0.670589798279379, 0.84152795885645, |
|
627 |
+5.93895353544503, 0.723329951949942, 0.733188455582477, 1.07557023464861, |
|
628 |
+1.09180382079188, 0.923957719945906, 0.93313538716072, 0.896562810368268, |
|
629 |
+1.09769821865825, 1.10615389985864, 0.94426955155254, 0.898545873061366, |
|
630 |
+0.876269943340891, 1.11556411094416, 0.94930544641744, 1.02495854041569, |
|
631 |
+0.794907983845338, 0.847332095413669, 0.776896984008625, 0.928896557877041, |
|
632 |
+0.945135371172636, 0.892100531723894), .Dim = c(128L, 8L), .Dimnames = list( |
|
633 |
+ NULL, c("CDKN2A", "KRAS", "MLL3", "PXDN", "SMAD4", "TGFBR2", |
|
634 |
+ "TP53", ""))) |
|
635 |
+ |
|
636 |
+ expect_equal(length( |
|
637 |
+ OncoSimulR:::peak_valley(OncoSimulR:::genot_to_adj_mat(cp2))$peak), 4) |
|
638 |
+ |
|
639 |
+ expect_equal(length( |
|
640 |
+ OncoSimulR:::peak_valley( |
|
641 |
+ OncoSimulR:::filter_inaccessible( |
|
642 |
+ OncoSimulR:::genot_to_adj_mat(cp2), 0))$peak), 6) |
|
643 |
+ |
|
644 |
+ |
|
645 |
+ expect_equal( |
|
646 |
+ OncoSimulR:::fast_peaks(cp2, 0), |
|
647 |
+ c(51, 55, 68, 74, 90, 107)) |
|
648 |
+ |
|
649 |
+ ## Nope, since filter inaccessible removes genotypes |
|
650 |
+ expect_false(all( |
|
651 |
+ OncoSimulR:::peak_valley( |
|
652 |
+ OncoSimulR:::filter_inaccessible( |
|
653 |
+ OncoSimulR:::genot_to_adj_mat(cp2), 0))$peak == |
|
654 |
+ OncoSimulR:::fast_peaks(cp2, 0))) |
|
655 |
+ |
|
656 |
+ |
|
657 |
+ ## compare with the probl |
|
658 |
+ gnn <- OncoSimulR:::to_Fitness_Matrix(cp2, 1000)$afe[, "Genotype"] |
|
659 |
+ |
|
660 |
+ plotFitnessLandscape(cp2, use_ggrepel = TRUE, only_accessible = TRUE) |
|
661 |
+ |
|
662 |
+ expect_equal( |
|
663 |
+ gnn[OncoSimulR:::fast_peaks(cp2, 0)], |
|
664 |
+ c("KRAS, PXDN, TP53", |
|
665 |
+ "MLL3, PXDN, SMAD4", |
|
666 |
+ "CDKN2A, KRAS, MLL3, TP53", |
|
667 |
+ "CDKN2A, KRAS, TGFBR2, TP53", |
|
668 |
+ "KRAS, MLL3, TGFBR2, TP53", |
|
669 |
+ "CDKN2A, KRAS, PXDN, SMAD4, TP53")) |
|
670 |
+ |
|
671 |
+ ## can also check by removing the inacessible genotypes so the indices are the same |
|
672 |
+ agg <- OncoSimulR:::wrap_accessibleGenotypes(cp2, 0) |
|
673 |
+ cp3 <- cp2[agg, ] |
|
674 |
+ |
|
675 |
+ ## This is NOT correct: we have removed the inacessible, |
|
676 |
+ ## but we allow backmutation |
|
677 |
+ ## OncoSimulR:::peak_valley( |
|
678 |
+ ## OncoSimulR:::genot_to_adj_mat(cp3))$peak |
|
679 |
+ |
|
680 |
+ expect_equal(OncoSimulR:::peak_valley( |
|
681 |
+ OncoSimulR:::filter_inaccessible( |
|
682 |
+ OncoSimulR:::genot_to_adj_mat(cp3), 0))$peak, |
|
683 |
+ OncoSimulR:::fast_peaks(cp3, 0)) |
|
684 |
+ |
|
685 |
+ gnn3 <- gnn[agg] |
|
686 |
+ |
|
687 |
+ expect_equal( |
|
688 |
+ gnn3[OncoSimulR:::fast_peaks(cp3, 0)], |
|
689 |
+ c("KRAS, PXDN, TP53", |
|
690 |
+ "MLL3, PXDN, SMAD4", |
|
691 |
+ "CDKN2A, KRAS, MLL3, TP53", |
|
692 |
+ "CDKN2A, KRAS, TGFBR2, TP53", |
|
693 |
+ "KRAS, MLL3, TGFBR2, TP53", |
|
694 |
+ "CDKN2A, KRAS, PXDN, SMAD4, TP53")) |
|
695 |
+ |
|
696 |
+ |
|
697 |
+}) |
|
698 |
+ |
|
699 |
+ |
|
700 |
+ |
|
701 |
+test_that("Some random checks of the fast peaks function", { |
|
702 |
+ niter <- 50 |
|
703 |
+ for(i in 1:niter) { |
|
704 |
+ for(ng in 2:6) { |
|
705 |
+ rtmp <- rfitness(ng) |
|
706 |
+ p1 <- OncoSimulR:::peak_valley( |
|
707 |
+ OncoSimulR:::filter_inaccessible( |
|
708 |
+ OncoSimulR:::genot_to_adj_mat(rtmp), 0))$peak |
|
709 |
+ expect_equal(length(p1), |
|
710 |
+ length(OncoSimulR:::fast_peaks(rtmp, 0))) |
|
711 |
+ agg <- OncoSimulR:::wrap_accessibleGenotypes(rtmp, 0) |
|
712 |
+ if(length(agg) >= 2) { |
|
713 |
+ ## cat(".") |
|
714 |
+ p2 <- OncoSimulR:::peak_valley( |
|
715 |
+ OncoSimulR:::filter_inaccessible( |
|
716 |
+ OncoSimulR:::genot_to_adj_mat(rtmp[agg, , drop = FALSE]), 0))$peak |
|
717 |
+ expect_equal(p2, OncoSimulR:::fast_peaks(rtmp[agg, , drop = FALSE], 0)) |
|
718 |
+ expect_equal(length(p2), length(p1)) |
|
719 |
+ } |
|
720 |
+ } |
|
721 |
+ } |
|
722 |
+}) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@119150 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,4 +1,4 @@ |
1 |
-test_that("Exercise plotting", { |
|
1 |
+test_that("Exercise plotting and dealing with different matrix input", { |
|
2 | 2 |
r1 <- rfitness(4) |
3 | 3 |
expect_silent(plot(r1)) |
4 | 4 |
expect_silent(plot(r1, log = TRUE)) |
... | ... |
@@ -7,8 +7,21 @@ test_that("Exercise plotting", { |
7 | 7 |
|
8 | 8 |
|
9 | 9 |
## Specify fitness in a matrix, and plot it |
10 |
- m5 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), c(1, 2, 3, 5.5)) |
|
10 |
+ m5 <- cbind(A = c(0, 1, 0, 1), B = c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
|
11 | 11 |
expect_silent(plotFitnessLandscape(m5)) |
12 |
+ |
|
13 |
+ m6 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), c(1, 2, 3, 5.5)) |
|
14 |
+ expect_message(plotFitnessLandscape(m6), |
|
15 |
+ "Setting/resetting gene names because", fixed = TRUE) |
|
16 |
+ |
|
17 |
+ m7 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
|
18 |
+ expect_message(plotFitnessLandscape(m7), |
|
19 |
+ "Setting/resetting gene names because", fixed = TRUE) |
|
20 |
+ |
|
21 |
+ m8 <- cbind(A = c(0, 1, 0, 1), c(0, 0, 1, 1), F = c(1, 2, 3, 5.5)) |
|
22 |
+ expect_message(plotFitnessLandscape(m8), |
|
23 |
+ "Setting/resetting gene names because", fixed = TRUE) |
|
24 |
+ |
|
12 | 25 |
|
13 | 26 |
## Specify fitness with allFitnessEffects, and plot it |
14 | 27 |
fe <- allFitnessEffects(epistasis = c("a : b" = 0.3, |
... | ... |
@@ -33,6 +46,18 @@ test_that("to_FitnessMatrix stops as it should", { |
33 | 46 |
expect_error(OncoSimulR:::to_Fitness_Matrix(x2, 2000), |
34 | 47 |
"We cannot guess what you are passing", |
35 | 48 |
fixed = TRUE) |
49 |
+ ## This is done above |
|
50 |
+ ## g <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1)) |
|
51 |
+ ## s1 <- c(1, 1.4, 1.2, 1.5) |
|
52 |
+ ## expect_error(OncoSimulR:::to_Fitness_Matrix(cbind(g, s1), 2000), |
|
53 |
+ ## "Matrix x must have column names", |
|
54 |
+ ## fixed = TRUE) |
|
55 |
+ ## expect_message(plotFitnessLandscape(cbind(g, s1)), |
|
56 |
+ ## "Matrix x must have column names", |
|
57 |
+ ## fixed = TRUE) |
|
58 |
+ ## expect_message(plotFitnessLandscape(cbind(g, A = c(1, 2))), |
|
59 |
+ ## "Matrix x must have column names", |
|
60 |
+ ## fixed = TRUE) |
|
36 | 61 |
}) |
37 | 62 |
|
38 | 63 |
|
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@118947 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,6 +1,10 @@ |
1 | 1 |
test_that("Exercise plotting", { |
2 | 2 |
r1 <- rfitness(4) |
3 | 3 |
expect_silent(plot(r1)) |
4 |
+ expect_silent(plot(r1, log = TRUE)) |
|
5 |
+ expect_silent(plot(r1, log = TRUE, use_ggrepel = TRUE)) |
|
6 |
+ expect_silent(plot(r1, log = TRUE, show_labels = FALSE)) |
|
7 |
+ |
|
4 | 8 |
|
5 | 9 |
## Specify fitness in a matrix, and plot it |
6 | 10 |
m5 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), c(1, 2, 3, 5.5)) |
... | ... |
@@ -12,14 +16,54 @@ test_that("Exercise plotting", { |
12 | 16 |
noIntGenes = c("e" = 0.1)) |
13 | 17 |
|
14 | 18 |
expect_silent(plot(evalAllGenotypes(fe, order = FALSE))) |
15 |
- |
|
19 |
+ |
|
16 | 20 |
## same as |
17 | 21 |
expect_silent(plotFitnessLandscape(evalAllGenotypes(fe, order = FALSE))) |
18 |
- |
|
22 |
+ ## more ggrepel |
|
23 |
+ expect_silent(plot(evalAllGenotypes(fe, order = FALSE), use_ggrepel = TRUE)) |
|
24 |
+}) |
|
25 |
+ |
|
26 |
+ |
|
27 |
+test_that("to_FitnessMatrix stops as it should", { |
|
28 |
+ x1 <- data.frame(a = 1:2, b = 1:2) |
|
29 |
+ expect_error(OncoSimulR:::to_Fitness_Matrix(x1, 2000), |
|
30 |
+ "We cannot guess what you are passing", |
|
31 |
+ fixed = TRUE) |
|
32 |
+ x2 <- list(a = 12, b = 13) |
|
33 |
+ expect_error(OncoSimulR:::to_Fitness_Matrix(x2, 2000), |
|
34 |
+ "We cannot guess what you are passing", |
|
35 |
+ fixed = TRUE) |
|
19 | 36 |
}) |
20 | 37 |
|
21 | 38 |
|
22 | 39 |
|
40 |
+test_that("to_FitnessMatrix can deal with df", { |
|
41 |
+ m4 <- data.frame(G = c("A, B", "A", "WT", "B"), |
|
42 |
+ Fitness = c(3, 2, 1, 4)) |
|
43 |
+ expect_message(OncoSimulR:::to_Fitness_Matrix(m4, 2000), |
|
44 |
+ "Column names of object", fixed = TRUE) |
|
45 |
+ m5 <- data.frame(G = c("A, B", "B"), |
|
46 |
+ Fitness = c(3, 2)) |
|
47 |
+ expect_message(OncoSimulR:::to_Fitness_Matrix(m5, 2000), |
|
48 |
+ "Column names of object", fixed = TRUE) |
|
49 |
+ x1 <- data.frame(a = c("A, B"), Fitness = 2) |
|
50 |
+ expect_message(OncoSimulR:::to_Fitness_Matrix(x1, 2000), |
|
51 |
+ "Column names of object", fixed = TRUE) |
|
52 |
+ x2 <- data.frame(a = c("A, B", "B"), Fitness = c(2, 3)) |
|
53 |
+ expect_message(OncoSimulR:::to_Fitness_Matrix(x2, 2000), |
|
54 |
+ "Column names of object", fixed = TRUE) |
|
55 |
+ x3 <- data.frame(a = c("A, B", "C"), Fitness = c(2, 3)) |
|
56 |
+ expect_message(OncoSimulR:::to_Fitness_Matrix(x3, 2000), |
|
57 |
+ "Column names of object", fixed = TRUE) |
|
58 |
+ ## Now, the user code |
|
59 |
+ expect_message(plotFitnessLandscape(x1)) |
|
60 |
+ expect_message(plotFitnessLandscape(x2)) |
|
61 |
+ expect_message(plotFitnessLandscape(x3)) |
|
62 |
+ expect_message(plotFitnessLandscape(m5)) |
|
63 |
+ expect_message(plotFitnessLandscape(m4)) |
|
64 |
+}) |
|
65 |
+ |
|
66 |
+ |
|
23 | 67 |
test_that("internal peak valley functions", { |
24 | 68 |
|
25 | 69 |
x <- matrix(NA, 14, 14) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@118909 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,205 @@ |
1 |
+test_that("Exercise plotting", { |
|
2 |
+ r1 <- rfitness(4) |
|
3 |
+ expect_silent(plot(r1)) |
|
4 |
+ |
|
5 |
+ ## Specify fitness in a matrix, and plot it |
|
6 |
+ m5 <- cbind(c(0, 1, 0, 1), c(0, 0, 1, 1), c(1, 2, 3, 5.5)) |
|
7 |
+ expect_silent(plotFitnessLandscape(m5)) |
|
8 |
+ |
|
9 |
+ ## Specify fitness with allFitnessEffects, and plot it |
|
10 |
+ fe <- allFitnessEffects(epistasis = c("a : b" = 0.3, |
|
11 |
+ "b : c" = 0.5), |
|
12 |
+ noIntGenes = c("e" = 0.1)) |
|
13 |
+ |
|
14 |
+ expect_silent(plot(evalAllGenotypes(fe, order = FALSE))) |
|
15 |
+ |
|
16 |
+ ## same as |
|
17 |
+ expect_silent(plotFitnessLandscape(evalAllGenotypes(fe, order = FALSE))) |
|
18 |
+ |
|
19 |
+}) |
|
20 |
+ |
|
21 |
+ |
|
22 |
+ |
|
23 |
+test_that("internal peak valley functions", { |
|
24 |
+ |
|
25 |
+ x <- matrix(NA, 14, 14) |
|
26 |
+ x[1, 3] <- -2 |
|
27 |
+ x[1, 2] <- -4 |
|
28 |
+ x[2, 3] <- 5 |
|
29 |
+ x[3, 4] <- 0 |
|
30 |
+ x[4, 5] <- 0 |
|
31 |
+ x[5, 6] <- 4 |
|
32 |
+ x[3, 7] <- -3 |
|
33 |
+ x[7, 8] <- 0 |
|
34 |
+ x[3, 10] <- -4 |
|
35 |
+ x[10, 11] <- -4 |
|
36 |
+ x[11, 12] <- 0 |
|
37 |
+ x[12, 13] <- 3 |
|
38 |
+ x[8, 9] <- 5 |
|
39 |
+ x[12, 14] <- -5 |
|
40 |
+ |
|
41 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
42 |
+ expect_equal(c(1, 6, 9, 13), pv$peak) |
|
43 |
+ expect_equal(c(2, 7, 8, 14), pv$valley) |
|
44 |
+ |
|
45 |
+ x <- matrix(NA, 15, 15) |
|
46 |
+ x[1, 3] <- -2 |
|
47 |
+ x[1, 2] <- -4 |
|
48 |
+ x[2, 3] <- 5 |
|
49 |
+ x[3, 4] <- 0 |
|
50 |
+ x[4, 5] <- 0 |
|
51 |
+ x[5, 6] <- 4 |
|
52 |
+ x[3, 7] <- -3 |
|
53 |
+ x[7, 8] <- 0 |
|
54 |
+ x[3, 10] <- -4 |
|
55 |
+ x[10, 11] <- -4 |
|
56 |
+ x[11, 12] <- 0 |
|
57 |
+ x[12, 13] <- 3 |
|
58 |
+ x[8, 9] <- 5 |
|
59 |
+ x[12, 14] <- -5 |
|
60 |
+ x[14, 15] <- 2 |
|
61 |
+ |
|
62 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
63 |
+ expect_equal(c(1, 6, 9, 13, 15), pv$peak) |
|
64 |
+ expect_equal(c(2, 7, 8, 14), pv$valley) |
|
65 |
+ |
|
66 |
+ |
|
67 |
+ x <- matrix(NA, 15, 15) |
|
68 |
+ x[1, 3] <- -2 |
|
69 |
+ x[1, 2] <- -4 |
|
70 |
+ x[2, 3] <- 5 |
|
71 |
+ x[3, 4] <- 3 |
|
72 |
+ x[4, 5] <- 0 |
|
73 |
+ x[5, 6] <- 4 |
|
74 |
+ x[3, 7] <- -3 |
|
75 |
+ x[7, 8] <- 0 |
|
76 |
+ x[3, 10] <- -4 |
|
77 |
+ x[10, 11] <- -4 |
|
78 |
+ x[11, 12] <- 0 |
|
79 |
+ x[12, 13] <- 3 |
|
80 |
+ x[8, 9] <- 5 |
|
81 |
+ x[12, 14] <- -5 |
|
82 |
+ x[14, 15] <- 2 |
|
83 |
+ |
|
84 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
85 |
+ expect_equal(c(1, 6, 9, 13, 15), pv$peak) |
|
86 |
+ expect_equal(c(2, 7, 8, 14), pv$valley) |
|
87 |
+ |
|
88 |
+ |
|
89 |
+ |
|
90 |
+ x <- matrix(NA, 15, 15) |
|
91 |
+ x[1, 3] <- -2 |
|
92 |
+ x[1, 2] <- -4 |
|
93 |
+ x[2, 3] <- 5 |
|
94 |
+ x[3, 4] <- 3 |
|
95 |
+ x[4, 5] <- -1 |
|
96 |
+ x[5, 6] <- 4 |
|
97 |
+ x[3, 7] <- -3 |
|
98 |
+ x[7, 8] <- 0 |
|
99 |
+ x[3, 10] <- -4 |
|
100 |
+ x[10, 11] <- -4 |
|
101 |
+ x[11, 12] <- 0 |
|
102 |
+ x[12, 13] <- 3 |
|
103 |
+ x[8, 9] <- 5 |
|
104 |
+ x[12, 14] <- -5 |
|
105 |
+ x[14, 15] <- 2 |
|
106 |
+ |
|
107 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
108 |
+ expect_equal(c(1, 4, 6, 9, 13, 15), pv$peak) |
|
109 |
+ expect_equal(c(2, 5, 7, 8, 14), pv$valley) |
|
110 |
+ |
|
111 |
+ |
|
112 |
+ x <- matrix(NA, 15, 15) |
|
113 |
+ x[1, 3] <- -2 |
|
114 |
+ x[1, 2] <- -4 |
|
115 |
+ x[2, 3] <- 5 |
|
116 |
+ x[3, 4] <- 3 |
|
117 |
+ x[4, 5] <- -1 |
|
118 |
+ x[5, 6] <- 4 |
|
119 |
+ x[3, 7] <- -3 |
|
120 |
+ x[7, 8] <- 0 |
|
121 |
+ x[3, 10] <- -4 |
|
122 |
+ x[10, 11] <- -4 |
|
123 |
+ x[11, 12] <- 0 |
|
124 |
+ x[12, 13] <- 3 |
|
125 |
+ x[8, 9] <- 5 |
|
126 |
+ x[12, 14] <- -5 |
|
127 |
+ x[14, 15] <- 2 |
|
128 |
+ x[2, 7] <- 1 |
|
129 |
+ |
|
130 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
131 |
+ expect_equal(c(1, 4, 6, 9, 13, 15), pv$peak) |
|
132 |
+ expect_equal(c(2, 5, 14), pv$valley) |
|
133 |
+ |
|
134 |
+ |
|
135 |
+ |
|
136 |
+ x <- matrix(NA, 15, 15) |
|
137 |
+ x[1, 3] <- -2 |
|
138 |
+ x[1, 2] <- -4 |
|
139 |
+ x[2, 3] <- 5 |
|
140 |
+ x[3, 4] <- 0 |
|
141 |
+ x[4, 5] <- -1 |
|
142 |
+ x[5, 6] <- 4 |
|
143 |
+ x[3, 7] <- -3 |
|
144 |
+ x[7, 8] <- 0 |
|
145 |
+ x[3, 10] <- -4 |
|
146 |
+ x[10, 11] <- -4 |
|
147 |
+ x[11, 12] <- 0 |
|
148 |
+ x[12, 13] <- 3 |
|
149 |
+ x[8, 9] <- 5 |
|
150 |
+ x[12, 14] <- -5 |
|
151 |
+ x[14, 15] <- 2 |
|
152 |
+ x[2, 7] <- 1 ## hummm.. 3 and 4 should be a peak?Nope, from 1 |
|
153 |
+ |
|
154 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
155 |
+ expect_equal(c(1, 6, 9, 13, 15), pv$peak) |
|
156 |
+ expect_equal(c(2, 5, 14), pv$valley) |
|
157 |
+ |
|
158 |
+ |
|
159 |
+ x <- matrix(NA, 15, 15) |
|
160 |
+ x[1, 3] <- 1 |
|
161 |
+ x[1, 2] <- -4 |
|
162 |
+ x[2, 3] <- 5 |
|
163 |
+ x[3, 4] <- 0 |
|
164 |
+ x[4, 5] <- -1 |
|
165 |
+ x[5, 6] <- 4 |
|
166 |
+ x[3, 7] <- -3 |
|
167 |
+ x[7, 8] <- 0 |
|
168 |
+ x[3, 10] <- -4 |
|
169 |
+ x[10, 11] <- -4 |
|
170 |
+ x[11, 12] <- 0 |
|
171 |
+ x[12, 13] <- 3 |
|
172 |
+ x[8, 9] <- 5 |
|
173 |
+ x[12, 14] <- -5 |
|
174 |
+ x[14, 15] <- 2 |
|
175 |
+ x[2, 7] <- 1 |
|
176 |
+ |
|
177 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
178 |
+ expect_equal(c(3, 4, 6, 9, 13, 15), pv$peak) |
|
179 |
+ expect_equal(c(2, 5, 14), pv$valley) |
|
180 |
+ |
|
181 |
+ |
|
182 |
+ |
|
183 |
+ x <- matrix(NA, 5, 5) |
|
184 |
+ x[1, 3] <- -2 |
|
185 |
+ x[2, 3] <- 4 |
|
186 |
+ x[3, 4] <- 0 |
|
187 |
+ x[4, 5] <- 6 |
|
188 |
+ |
|
189 |
+ (pv <- OncoSimulR:::peak_valley(x)) |
|
190 |
+ expect_equal(c(1, 5), pv$peak) |
|
191 |
+ expect_equal(c(2), pv$valley) |
|
192 |
+ |
|
193 |
+ |
|
194 |
+ x <- matrix(NA, 5, 5) |
|
195 |
+ x[1, 3] <- -2 |
|
196 |
+ x[2, 3] <- -5 |
|
197 |
+ x[3, 4] <- 0 |
|
198 |
+ x[4, 5] <- 6 |
|