git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/OncoSimulR@118942 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.3.4 |
|
5 |
-Date: 2016-06-24 |
|
4 |
+Version: 2.3.5 |
|
5 |
+Date: 2016-06-25 |
|
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")) |
... | ... |
@@ -8,7 +8,8 @@ export("oncoSimulPop", "oncoSimulIndiv", "samplePop", |
8 | 8 |
"evalGenotypeMut", "evalGenotypeFitAndMut", |
9 | 9 |
"evalAllGenotypesFitAndMut", |
10 | 10 |
"rfitness", |
11 |
- "plotFitnessLandscape" |
|
11 |
+ "plotFitnessLandscape", |
|
12 |
+ "to_Magellan" |
|
12 | 13 |
) |
13 | 14 |
|
14 | 15 |
S3method(plot, oncosimul) |
... | ... |
@@ -24,7 +25,7 @@ S3method(plot, evalAllGenotypesMut) |
24 | 25 |
|
25 | 26 |
import(ggplot2) |
26 | 27 |
importFrom("ggrepel", geom_text_repel, geom_label_repel) |
27 |
- |
|
28 |
+importFrom("utils", "read.table", "write.table") |
|
28 | 29 |
importFrom("stats", "rnorm") |
29 | 30 |
importFrom("data.table", rbindlist, .rbind.data.table) |
30 | 31 |
importFrom(Rcpp, evalCpp) |
... | ... |
@@ -54,53 +54,54 @@ plotFitnessLandscape <- function(x, show_labels = TRUE, |
54 | 54 |
## get the string representation, etc. And this is for use |
55 | 55 |
## with OncoSimul. |
56 | 56 |
|
57 |
- ## FIXME: passing fitness as a 2 column data frame |
|
58 |
- |
|
59 |
- if( (inherits(x, "genotype_fitness_matrix")) || |
|
60 |
- ( (is.matrix(x) || is.data.frame(x)) && (ncol(x) > 2) ) ) { |
|
61 |
- ## Why this? We go back and forth twice. We need both things. We |
|
62 |
- ## could construct the afe below by appropriately pasting the |
|
63 |
- ## columns names |
|
64 |
- afe <- evalAllGenotypes(allFitnessEffects( |
|
65 |
- epistasis = from_genotype_fitness(x)), |
|
66 |
- order = FALSE, addwt = TRUE, max = max_num_genotypes) |
|
67 |
- ## Might not be needed with the proper gfm object (so gmf <- x) |
|
68 |
- ## but is needed if arbitrary matrices. |
|
69 |
- gfm <- allGenotypes_to_matrix(afe) |
|
70 |
- } else if(inherits(x, "fitnessEffects")) { |
|
71 |
- if(!is.null(x$orderEffects) ) |
|
72 |
- stop("We cannot yet deal with order effects") |
|
73 |
- afe <- evalAllGenotypes(x, |
|
74 |
- order = FALSE, |
|
75 |
- addwt = TRUE, max = max_num_genotypes) |
|
76 |
- gfm <- allGenotypes_to_matrix(afe) |
|
77 |
- } else if( (inherits(x, "evalAllGenotypes")) || |
|
78 |
- (inherits(x, "evalAllGenotypesMut"))) { |
|
79 |
- if(any(grepl(">", x[, 1], fixed = TRUE))) |
|
80 |
- stop("We cannot deal with order effects yet.") |
|
81 |
- x <- x[, c(1, 2)] |
|
82 |
- if(x[1, "Genotype"] != "WT") { |
|
83 |
- ## Yes, because we expect this present below |
|
84 |
- x <- rbind(data.frame(Genotype = "WT", |
|
85 |
- Fitness = 1, |
|
86 |
- stringsAsFactors = FALSE), |
|
87 |
- x) |
|
88 |
- } |
|
89 |
- afe <- x |
|
90 |
- ## in case we pass an evalAllgenotypesfitandmut |
|
91 |
- gfm <- allGenotypes_to_matrix(afe) |
|
92 |
- } else if(is.data.frame(x)) { |
|
93 |
- ## Assume a two-column data frame of genotypes as character |
|
94 |
- ## vectors and fitness |
|
95 |
- if(colnames(x)[2] != "Fitness") |
|
96 |
- stop("We cannot guess what you are passing here") |
|
97 |
- afe <- evalAllGenotypes(allFitnessEffects(genotFitness = x), |
|
98 |
- order = FALSE, addwt = TRUE, |
|
99 |
- max = max_num_genotypes) |
|
100 |
- gfm <- allGenotypes_to_matrix(afe) |
|
101 |
- } else { |
|
102 |
- stop("We cannot guess what you are passing here") |
|
103 |
- } |
|
57 |
+ |
|
58 |
+ tfm <- to_Fitness_Matrix(x, max_num_genotypes = max_num_genotypes) |
|
59 |
+ |
|
60 |
+ ## if( (inherits(x, "genotype_fitness_matrix")) || |
|
61 |
+ ## ( (is.matrix(x) || is.data.frame(x)) && (ncol(x) > 2) ) ) { |
|
62 |
+ ## ## Why this? We go back and forth twice. We need both things. We |
|
63 |
+ ## ## could construct the afe below by appropriately pasting the |
|
64 |
+ ## ## columns names |
|
65 |
+ ## afe <- evalAllGenotypes(allFitnessEffects( |
|
66 |
+ ## epistasis = from_genotype_fitness(x)), |
|
67 |
+ ## order = FALSE, addwt = TRUE, max = max_num_genotypes) |
|
68 |
+ ## ## Might not be needed with the proper gfm object (so gmf <- x) |
|
69 |
+ ## ## but is needed if arbitrary matrices. |
|
70 |
+ ## gfm <- allGenotypes_to_matrix(afe) |
|
71 |
+ ## } else if(inherits(x, "fitnessEffects")) { |
|
72 |
+ ## if(!is.null(x$orderEffects) ) |
|
73 |
+ ## stop("We cannot yet deal with order effects") |
|
74 |
+ ## afe <- evalAllGenotypes(x, |
|
75 |
+ ## order = FALSE, |
|
76 |
+ ## addwt = TRUE, max = max_num_genotypes) |
|
77 |
+ ## gfm <- allGenotypes_to_matrix(afe) |
|
78 |
+ ## } else if( (inherits(x, "evalAllGenotypes")) || |
|
79 |
+ ## (inherits(x, "evalAllGenotypesMut"))) { |
|
80 |
+ ## if(any(grepl(">", x[, 1], fixed = TRUE))) |
|
81 |
+ ## stop("We cannot deal with order effects yet.") |
|
82 |
+ ## x <- x[, c(1, 2)] |
|
83 |
+ ## if(x[1, "Genotype"] != "WT") { |
|
84 |
+ ## ## Yes, because we expect this present below |
|
85 |
+ ## x <- rbind(data.frame(Genotype = "WT", |
|
86 |
+ ## Fitness = 1, |
|
87 |
+ ## stringsAsFactors = FALSE), |
|
88 |
+ ## x) |
|
89 |
+ ## } |
|
90 |
+ ## afe <- x |
|
91 |
+ ## ## in case we pass an evalAllgenotypesfitandmut |
|
92 |
+ ## gfm <- allGenotypes_to_matrix(afe) |
|
93 |
+ ## } else if(is.data.frame(x)) { |
|
94 |
+ ## ## Assume a two-column data frame of genotypes as character |
|
95 |
+ ## ## vectors and fitness |
|
96 |
+ ## if(colnames(x)[2] != "Fitness") |
|
97 |
+ ## stop("We cannot guess what you are passing here") |
|
98 |
+ ## afe <- evalAllGenotypes(allFitnessEffects(genotFitness = x), |
|
99 |
+ ## order = FALSE, addwt = TRUE, |
|
100 |
+ ## max = max_num_genotypes) |
|
101 |
+ ## gfm <- allGenotypes_to_matrix(afe) |
|
102 |
+ ## } else { |
|
103 |
+ ## stop("We cannot guess what you are passing here") |
|
104 |
+ ## } |
|
104 | 105 |
|
105 | 106 |
|
106 | 107 |
|
... | ... |
@@ -155,8 +156,8 @@ plotFitnessLandscape <- function(x, show_labels = TRUE, |
155 | 156 |
## } |
156 | 157 |
## } |
157 | 158 |
|
158 |
- mutated <- rowSums(gfm[, -ncol(gfm)]) |
|
159 |
- gaj <- genot_to_adj_mat(gfm) |
|
159 |
+ mutated <- rowSums(tfm$gfm[, -ncol(tfm$gfm)]) |
|
160 |
+ gaj <- genot_to_adj_mat(tfm$gfm) |
|
160 | 161 |
vv <- which(!is.na(gaj), arr.ind = TRUE) |
161 | 162 |
|
162 | 163 |
## plot(x = mutated, y = e1$Fitness, ylab = "Fitness", |
... | ... |
@@ -172,13 +173,13 @@ plotFitnessLandscape <- function(x, show_labels = TRUE, |
172 | 173 |
|
173 | 174 |
|
174 | 175 |
dd <- data.frame(muts = mutated, |
175 |
- fitness = afe$Fitness, |
|
176 |
- label = afe$Genotype) |
|
176 |
+ fitness = tfm$afe$Fitness, |
|
177 |
+ label = tfm$afe$Genotype) |
|
177 | 178 |
cl <- gaj[vv] |
178 | 179 |
sg <- data.frame(x_from = mutated[vv[, 1]], |
179 |
- y_from = afe$Fitness[vv[, 1]], |
|
180 |
+ y_from = tfm$afe$Fitness[vv[, 1]], |
|
180 | 181 |
x_to = mutated[vv[, 2]], |
181 |
- y_to = afe$Fitness[vv[, 2]], |
|
182 |
+ y_to = tfm$afe$Fitness[vv[, 2]], |
|
182 | 183 |
Change = factor(ifelse(cl == 0, "Neutral", |
183 | 184 |
ifelse(cl > 0, "Gain", "Loss")))) |
184 | 185 |
## From http://stackoverflow.com/a/17257422 |
... | ... |
@@ -17,6 +17,73 @@ |
17 | 17 |
|
18 | 18 |
## Functions that allow passing a matrix or data frame of mappings |
19 | 19 |
## genotype -> fitness so this is taken as input in fitnessEffects. |
20 |
+## and some related functions |
|
21 |
+ |
|
22 |
+ |
|
23 |
+ |
|
24 |
+to_Magellan <- function(x, file, |
|
25 |
+ max_num_genotypes = 2000) { |
|
26 |
+ if(is.null(file)) { |
|
27 |
+ file <- tempfile() |
|
28 |
+ cat("\n Using file ", file, "\n") |
|
29 |
+ } |
|
30 |
+ gfm <- to_Fitness_Matrix(x, max_num_genotypes = max_num_genotypes)$gfm |
|
31 |
+ write(rep(2, ncol(gfm) - 1), file = file, ncolumns = ncol(gfm) - 1) |
|
32 |
+ write.table(gfm, file = file, append = TRUE, |
|
33 |
+ row.names = FALSE, col.names = FALSE, sep = " ") |
|
34 |
+} |
|
35 |
+ |
|
36 |
+to_Fitness_Matrix <- function(x, max_num_genotypes) { |
|
37 |
+ ## A general converter. Ready to be used by plotFitnessLandscape and |
|
38 |
+ ## Magellan exporter. |
|
39 |
+ |
|
40 |
+ if( (inherits(x, "genotype_fitness_matrix")) || |
|
41 |
+ ( (is.matrix(x) || is.data.frame(x)) && (ncol(x) > 2) ) ) { |
|
42 |
+ ## Why this? We go back and forth twice. We need both things. We |
|
43 |
+ ## could construct the afe below by appropriately pasting the |
|
44 |
+ ## columns names |
|
45 |
+ afe <- evalAllGenotypes(allFitnessEffects( |
|
46 |
+ epistasis = from_genotype_fitness(x)), |
|
47 |
+ order = FALSE, addwt = TRUE, max = max_num_genotypes) |
|
48 |
+ ## Might not be needed with the proper gfm object (so gmf <- x) |
|
49 |
+ ## but is needed if arbitrary matrices. |
|
50 |
+ gfm <- allGenotypes_to_matrix(afe) |
|
51 |
+ } else if(inherits(x, "fitnessEffects")) { |
|
52 |
+ if(!is.null(x$orderEffects) ) |
|
53 |
+ stop("We cannot yet deal with order effects") |
|
54 |
+ afe <- evalAllGenotypes(x, |
|
55 |
+ order = FALSE, |
|
56 |
+ addwt = TRUE, max = max_num_genotypes) |
|
57 |
+ gfm <- allGenotypes_to_matrix(afe) |
|
58 |
+ } else if( (inherits(x, "evalAllGenotypes")) || |
|
59 |
+ (inherits(x, "evalAllGenotypesMut"))) { |
|
60 |
+ if(any(grepl(">", x[, 1], fixed = TRUE))) |
|
61 |
+ stop("We cannot deal with order effects yet.") |
|
62 |
+ x <- x[, c(1, 2)] |
|
63 |
+ if(x[1, "Genotype"] != "WT") { |
|
64 |
+ ## Yes, because we expect this present below |
|
65 |
+ x <- rbind(data.frame(Genotype = "WT", |
|
66 |
+ Fitness = 1, |
|
67 |
+ stringsAsFactors = FALSE), |
|
68 |
+ x) |
|
69 |
+ } |
|
70 |
+ afe <- x |
|
71 |
+ ## in case we pass an evalAllgenotypesfitandmut |
|
72 |
+ gfm <- allGenotypes_to_matrix(afe) |
|
73 |
+ } else if(is.data.frame(x)) { |
|
74 |
+ ## Assume a two-column data frame of genotypes as character |
|
75 |
+ ## vectors and fitness |
|
76 |
+ if(colnames(x)[2] != "Fitness") |
|
77 |
+ stop("We cannot guess what you are passing here") |
|
78 |
+ afe <- evalAllGenotypes(allFitnessEffects(genotFitness = x), |
|
79 |
+ order = FALSE, addwt = TRUE, |
|
80 |
+ max = max_num_genotypes) |
|
81 |
+ gfm <- allGenotypes_to_matrix(afe) |
|
82 |
+ } else { |
|
83 |
+ stop("We cannot guess what you are passing here") |
|
84 |
+ } |
|
85 |
+ return(list(gfm = gfm, afe = afe)) |
|
86 |
+} |
|
20 | 87 |
|
21 | 88 |
|
22 | 89 |
from_genotype_fitness <- function(x) { |
... | ... |
@@ -157,20 +224,37 @@ allGenotypes_to_matrix <- function(x) { |
157 | 224 |
} |
158 | 225 |
|
159 | 226 |
|
227 |
+ |
|
228 |
+magellan_stats <- function(x, max_num_genotypes = 2000, |
|
229 |
+ verbose = FALSE, |
|
230 |
+ fl_statistics = "fl_statistics") { |
|
231 |
+ ## if(!is.null(x) && is.null(file)) |
|
232 |
+ ## stop("one of object or file name") |
|
233 |
+ ## if(is.null(file)) |
|
234 |
+ fn <- tempfile() |
|
235 |
+ fnret <- tempfile() |
|
236 |
+ if(verbose) |
|
237 |
+ cat("\n Using input file", fn, " and output file ", fnret, "\n") |
|
238 |
+ to_Magellan(x, fn, max_num_genotypes = max_num_genotypes) |
|
239 |
+ call_M <- system(paste(fl_statistics, fn, "-s", "-o", fnret)) |
|
240 |
+ return(read.table(fnret, skip = 1, header = TRUE)[-1]) |
|
241 |
+} |
|
242 |
+ |
|
243 |
+ |
|
160 | 244 |
## |
161 | 245 |
|
162 |
-## Example of Bozic issues |
|
163 |
-m1 <- cbind(c(0, 1), c(1, 0), c(2, 3)) |
|
246 |
+## ## Example of Bozic issues |
|
247 |
+## m1 <- cbind(c(0, 1), c(1, 0), c(2, 3)) |
|
164 | 248 |
|
165 |
-m2 <- cbind(c(1, 1), c(1, 0), c(2, 3)) |
|
249 |
+## m2 <- cbind(c(1, 1), c(1, 0), c(2, 3)) |
|
166 | 250 |
|
167 |
-m3 <- data.frame(G = c("A, B", "A"), F = c(1, 2)) |
|
251 |
+## m3 <- data.frame(G = c("A, B", "A"), F = c(1, 2)) |
|
168 | 252 |
|
169 |
-m4 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2, 1, 4)) |
|
253 |
+## m4 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2, 1, 4)) |
|
170 | 254 |
|
171 |
-m5 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2, 1, 0)) |
|
255 |
+## m5 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2, 1, 0)) |
|
172 | 256 |
|
173 |
-m6 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2.5, 2, 0)) |
|
257 |
+## m6 <- data.frame(G = c("A, B", "A", "WT", "B"), F = c(3, 2.5, 2, 0)) |
|
174 | 258 |
|
175 | 259 |
|
176 | 260 |
|
... | ... |
@@ -1,18 +1,21 @@ |
1 |
+Changes in version 2.3.5 (2016-06-25): |
|
2 |
+ - to_Magellan. |
|
3 |
+ |
|
1 | 4 |
Changes in version 2.3.4 (2016-06-24): |
2 | 5 |
- Failing some tests in Win 32-bits |
3 | 6 |
|
4 | 7 |
Changes in version 2.3.3 (2016-06-23): |
5 | 8 |
- Vignette improvements and typo fixes. |
6 |
- - rfitness |
|
7 |
- - Plot of fitness landscapes |
|
8 |
- - Specify fitness by giving genotype-> fitness mapping |
|
9 |
- - Tests showing same gene in epist./DAG/order |
|
10 |
- - Clarified internal C++ unique/sorted in genotypes |
|
11 |
- - Checks initMutant correct and bug initMutant mutable pos |
|
9 |
+ - rfitness: generate fitness landscapes. |
|
10 |
+ - Plot of fitness landscapes. |
|
11 |
+ - Specify fitness by giving genotype-> fitness mapping. |
|
12 |
+ - Tests showing same gene in epist./DAG/order. |
|
13 |
+ - Clarified internal C++ unique/sorted in genotypes. |
|
14 |
+ - Checks initMutant correct and bug initMutant mutable pos. |
|
12 | 15 |
- samplePop: sample at arbitrary sizes. |
13 | 16 |
- plot.oncosimulpop using auto for color. |
14 | 17 |
- Mutator phenotype and gene-specific mutation rates. |
15 |
- - Bug fixed: to_update set at 2 when mutating to pre-existing; |
|
18 |
+ - Bug fixed: to_update set at 2 when mutating to pre-existing. |
|
16 | 19 |
- Lots and lots of new tests. |
17 | 20 |
|
18 | 21 |
Changes in version 2.2.0 (for BioC 3.3): |
... | ... |
@@ -389,9 +389,9 @@ evalAllGenotypes(fem6, addwt = TRUE, order = FALSE) |
389 | 389 |
## Plotting a fitness landscape |
390 | 390 |
|
391 | 391 |
fe2 <- allFitnessEffects(noIntGenes = |
392 |
- c(a1 = 0.1, a2 = 0.2, |
|
393 |
- b1 = 0.01, b2 = 0.3, b3 = 0.2, |
|
394 |
- c1 = 0.3, c2 = -0.2)) |
|
392 |
+ c(a1 = 0.1, |
|
393 |
+ b1 = 0.01, |
|
394 |
+ c1 = 0.3)) |
|
395 | 395 |
|
396 | 396 |
plot(evalAllGenotypes(fe2, order = FALSE)) |
397 | 397 |
|
... | ... |
@@ -109,7 +109,7 @@ Ramon Diaz-Uriarte |
109 | 109 |
\references{ |
110 | 110 |
MAGELLAN web site: \url{http://wwwabi.snv.jussieu.fr/public/Magellan/} |
111 | 111 |
|
112 |
- Brouillet, S. et al. (2015). MAGELLAN: a tool to explore small fitness landscapes. \emph{bioRxiv\/}, \bold{31583}. \url{http://doi.org/10.1101/031583} |
|
112 |
+ Brouillet, S. et al. (2015). MAGELLAN: a tool to explore small fitness landscapes. \emph{bioRxiv}, \bold{31583}. \url{http://doi.org/10.1101/031583} |
|
113 | 113 |
|
114 | 114 |
} |
115 | 115 |
|
... | ... |
@@ -118,18 +118,17 @@ Ramon Diaz-Uriarte |
118 | 118 |
|
119 | 119 |
I have copied most of the ideas (and colors, and labels) of this plot |
120 | 120 |
from MAGELLAN (\url{http://wwwabi.snv.jussieu.fr/public/Magellan/}) |
121 |
- but MAGELLAN has other functionality that is not provided here (e.g., |
|
121 |
+ but MAGELLAN has other functionality that is not provided here such as |
|
122 | 122 |
epistasis stats for the landscape, and several visual manipulation |
123 |
- options). |
|
124 |
- |
|
125 |
- In addition to cosmetic differences, an important difference between |
|
126 |
- this plot and those of MAGELLAN is \bold{how sinks/peaks of more than |
|
127 |
- one genotype are dealt with}. This plot will correctly show as sinks |
|
128 |
- or peaks sets of one or more genotypes that are of identical fitness |
|
129 |
- (and separated by a Haming distance of one). So a sink or a peak might |
|
130 |
- actually be made of more than one genotype. MAGELLAN, as far as I can |
|
131 |
- tell, cannot do this: peaks and sinks are always made of a single |
|
132 |
- isolated genotype. |
|
123 |
+ options. |
|
124 |
+ |
|
125 |
+ In addition to the above differences, another difference between this |
|
126 |
+ plot and those of MAGELLAN is \bold{how sinks/peaks of more than one |
|
127 |
+ genotype are dealt with}. This plot will show as sinks or peaks sets |
|
128 |
+ of one or more genotypes that are of identical fitness (and separated |
|
129 |
+ by a Haming distance of one). So a sink or a peak might actually be |
|
130 |
+ made of more than one genotype. In MAGELLAN, as far as I can tell, |
|
131 |
+ peaks and sinks are always made of a single isolated genotype. |
|
133 | 132 |
|
134 | 133 |
Does this matter? In most realistic cases where not two genotypes can |
135 | 134 |
have exactly the same fittnes it does not. In some cases, though, it |
136 | 135 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,107 @@ |
1 |
+\name{to_Magellan} |
|
2 |
+\alias{to_Magellan} |
|
3 |
+ |
|
4 |
+\title{ Create output for MAGELLAN. } |
|
5 |
+ |
|
6 |
+\description{ Create a fitness landscape in a format that is understood |
|
7 |
+ by MAGELLAN \url{http://wwwabi.snv.jussieu.fr/public/Magellan/}. |
|
8 |
+ |
|
9 |
+} |
|
10 |
+ |
|
11 |
+\usage{ |
|
12 |
+to_Magellan(x, file, |
|
13 |
+ max_num_genotypes = 2000) |
|
14 |
+} |
|
15 |
+ |
|
16 |
+\arguments{ |
|
17 |
+ |
|
18 |
+ \item{x}{ One of the following: |
|
19 |
+ \itemize{ |
|
20 |
+ |
|
21 |
+ \item A matrix (or data frame) with g + 1 columns. Each of the |
|
22 |
+ first g columns contains a 1 or a 0 indicating that the gene of |
|
23 |
+ that column is mutated or not. Column g+ 1 contains the fitness |
|
24 |
+ values. This is, for instance, the output you will get from |
|
25 |
+ \code{\link{rfitness}}. |
|
26 |
+ |
|
27 |
+ \item A two column data frame. The second column is fitness, and |
|
28 |
+ the first column are genotypes, given as a character vector. For |
|
29 |
+ instance, a row "A, B" would mean the genotype with both A and B |
|
30 |
+ mutated. |
|
31 |
+ |
|
32 |
+ \item The output from a call to |
|
33 |
+ \code{\link{evalAllGenotypes}}. Make sure you use \code{order = |
|
34 |
+ FALSE} in that call. |
|
35 |
+ |
|
36 |
+ \item The output from a call to |
|
37 |
+ \code{\link{evalAllGenotypesMut}}. Make sure you use \code{order = |
|
38 |
+ FALSE}. |
|
39 |
+ |
|
40 |
+ \item The output from a call to \code{\link{allFitnessEffects}} |
|
41 |
+ (with no order effects in the specification). |
|
42 |
+ |
|
43 |
+ } |
|
44 |
+ |
|
45 |
+ The first two are the same as the format for the \code{genotFitness} |
|
46 |
+ component in \code{\link{allFitnessEffects}}. } |
|
47 |
+ |
|
48 |
+ \item{file}{The name of the output file. If NULL, a name will be |
|
49 |
+ created using \code{\link{tempfile}}.} |
|
50 |
+ |
|
51 |
+ \item{max_num_genotypes}{Maximum allowed number of genotypes. For some |
|
52 |
+ types of input, we make a call to \code{\link{evalAllGenotypes}}, and |
|
53 |
+ use this as the maximum.} |
|
54 |
+ |
|
55 |
+} |
|
56 |
+ |
|
57 |
+\value{ |
|
58 |
+ |
|
59 |
+ A file is written to disk. You can then plot and/or show summary |
|
60 |
+ statistics using MAGELLAN. |
|
61 |
+} |
|
62 |
+ |
|
63 |
+\note{ |
|
64 |
+ If you try to pass a fitness specification with order effects you will |
|
65 |
+ receive an error, since that cannot be plotted with MAGELLAN. |
|
66 |
+} |
|
67 |
+ |
|
68 |
+\author{ |
|
69 |
+Ramon Diaz-Uriarte |
|
70 |
+} |
|
71 |
+ |
|
72 |
+\references{ |
|
73 |
+ MAGELLAN web site: \url{http://wwwabi.snv.jussieu.fr/public/Magellan/} |
|
74 |
+ |
|
75 |
+ Brouillet, S. et al. (2015). MAGELLAN: a tool to explore small fitness landscapes. \emph{bioRxiv}, \bold{31583}. \url{http://doi.org/10.1101/031583} |
|
76 |
+ |
|
77 |
+} |
|
78 |
+ |
|
79 |
+ |
|
80 |
+ |
|
81 |
+\seealso{ |
|
82 |
+ \code{\link{allFitnessEffects}}, |
|
83 |
+ \code{\link{evalAllGenotypes}}, |
|
84 |
+ \code{\link{allFitnessEffects}}, |
|
85 |
+ \code{\link{rfitness}} |
|
86 |
+} |
|
87 |
+\examples{ |
|
88 |
+ |
|
89 |
+## Generate random fitness for four-genes genotype |
|
90 |
+## and export landscape. |
|
91 |
+ |
|
92 |
+r1 <- rfitness(4) |
|
93 |
+to_Magellan(r1, NULL) |
|
94 |
+ |
|
95 |
+## Specify fitness using a DAG and export it |
|
96 |
+cs <- data.frame(parent = c(rep("Root", 3), "a", "d", "c"), |
|
97 |
+ child = c("a", "b", "d", "e", "c", "f"), |
|
98 |
+ s = 0.1, |
|
99 |
+ sh = -0.9, |
|
100 |
+ typeDep = "MN") |
|
101 |
+ |
|
102 |
+to_Magellan(allFitnessEffects(cs), NULL) |
|
103 |
+ |
|
104 |
+} |
|
105 |
+ |
|
106 |
+\keyword{ manip } |
|
107 |
+ |
... | ... |
@@ -2586,8 +2586,9 @@ maxima and get an idea of how the fitness landscape looks. |
2586 | 2586 |
In \Rfunction{plotFitnessLandscape} I have blatantly and shamelessly |
2587 | 2587 |
copied most of the looks of the plots of MAGELLAN |
2588 | 2588 |
(\url{http://wwwabi.snv.jussieu.fr/public/Magellan/}, |
2589 |
-\cite{brouillet_magellan:_2015}), a nice web-based tool for fitness |
|
2590 |
-landscape plotting and analysis. |
|
2589 |
+\cite{brouillet_magellan:_2015}), a very nice web-based tool for fitness |
|
2590 |
+landscape plotting and analysis (MAGELLAN provide some other extra |
|
2591 |
+functionality and epistasis statistics not provided here). |
|
2591 | 2592 |
|
2592 | 2593 |
As an example, let us show the previous example of Weissman et al. we saw |
2593 | 2594 |
in \ref{weissmanex}: |
... | ... |
@@ -2612,17 +2613,17 @@ wb <- allFitnessEffects( |
2612 | 2613 |
@ |
2613 | 2614 |
|
2614 | 2615 |
\clearpage |
2615 |
-<<>>= |
|
2616 |
-plotFitnessLandscape(wb, use_ggrepel = TRUE) ## ggrepel to avoid overlap |
|
2617 |
- ## of labels |
|
2618 |
- |
|
2616 |
+<<fig.width=6.5, fig.height=6>>= |
|
2617 |
+plotFitnessLandscape(wb, use_ggrepel = TRUE) |
|
2619 | 2618 |
@ |
2620 | 2619 |
|
2620 |
+We have set \texttt{use\_ggrepel = TRUE} to avoid overlap of labels. |
|
2621 |
+ |
|
2621 | 2622 |
\clearpage |
2622 | 2623 |
For some types of objects, directly invoking \Rfunction{plot} will give |
2623 | 2624 |
you the fitness plot |
2624 | 2625 |
|
2625 |
-<<>>= |
|
2626 |
+<<fig.width=6.5, fig.height=6>>= |
|
2626 | 2627 |
(ewb <- evalAllGenotypes(wb, order = FALSE)) |
2627 | 2628 |
plot(ewb, use_ggrepel = TRUE) |
2628 | 2629 |
|
... | ... |
@@ -2711,7 +2712,7 @@ And if you compare the tabular output of \Rfunction{evalAllGenotypes} you can |
2711 | 2712 |
see that the values of fitness reproduces the fitness landscape that they |
2712 | 2713 |
show in their Figure 1. We can also use our plot for fitness landscapes: |
2713 | 2714 |
|
2714 |
-<<>>= |
|
2715 |
+<<fig.width=6, fig.height=6>>= |
|
2715 | 2716 |
plot(b1, use_ggrepel = TRUE) |
2716 | 2717 |
@ |
2717 | 2718 |
|
... | ... |
@@ -1,15 +1,15 @@ |
1 | 1 |
\usepackage[% |
2 |
- shash={3486983}, |
|
3 |
- lhash={348698385e2f09528be7eb816768bd8ec06b7e70}, |
|
2 |
+ shash={a8daef6}, |
|
3 |
+ lhash={a8daef6cae6f3c218599ea59264b950e95040f54}, |
|
4 | 4 |
authname={Ramon Diaz-Uriarte}, |
5 | 5 |
authemail={rdiaz02@users.noreply.github.com}, |
6 |
- authsdate={2016-06-23}, |
|
7 |
- authidate={2016-06-23 19:01:20 +0200}, |
|
8 |
- authudate={1466701280}, |
|
6 |
+ authsdate={2016-06-24}, |
|
7 |
+ authidate={2016-06-24 10:14:31 +0200}, |
|
8 |
+ authudate={1466756071}, |
|
9 | 9 |
commname={Ramon Diaz-Uriarte}, |
10 | 10 |
commemail={rdiaz02@users.noreply.github.com}, |
11 |
- commsdate={2016-06-23}, |
|
12 |
- commidate={2016-06-23 19:01:20 +0200}, |
|
13 |
- commudate={1466701280}, |
|
11 |
+ commsdate={2016-06-24}, |
|
12 |
+ commidate={2016-06-24 10:14:31 +0200}, |
|
13 |
+ commudate={1466756071}, |
|
14 | 14 |
refnames={ (HEAD, origin/master, origin/HEAD)} |
15 | 15 |
]{gitsetinfo} |
16 | 16 |
\ No newline at end of file |