Browse code

initMutant: fixed bug and added to vignette

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

Ramon Diaz-Uriarte authored on 25/06/2015 12:28:13
Showing 10 changed files

... ...
@@ -1,8 +1,8 @@
1 1
 Package: OncoSimulR
2 2
 Type: Package
3 3
 Title: Forward Genetic Simulation of Cancer Progresion with Epistasis 
4
-Version: 1.99.4
5
-Date: 2015-06-22
4
+Version: 1.99.5
5
+Date: 2015-06-25
6 6
 Author: Ramon Diaz-Uriarte. Melissa O'Neill for randutils.
7 7
 Maintainer: Ramon Diaz-Uriarte <rdiaz02@gmail.com>
8 8
 Description: Functions for forward population genetic simulation in
... ...
@@ -356,9 +356,25 @@ getNamesID <- function(fp) {
356 356
 }
357 357
 
358 358
 
359
-getDrv <- function(geneModule, geneNoInt, drv) {
360
-    indicesM <- sort(match( drv, geneModule$Gene))
361
-    indicesI <- sort(match( drv, geneNoInt$Gene))
359
+getGeneIDNum <- function(geneModule, geneNoInt, drv, sort = TRUE) {
360
+    ## It returns the genes, as NumID, in the given vector with names drv
361
+    ## initMutant uses this, for simplicity, without sorting, but noInt
362
+    ## are always sorted
363
+
364
+    ## Also used for the drivers with sort = TRUE
365
+
366
+    ## Yes, we must do it twice because we do not know before hand which
367
+    ## is which. This makes sure no NA. Period.
368
+    if(any(is.na( match(drv, c(geneModule$Gene, geneNoInt$Gene))))) {
369
+        stop(paste("For driver or initMutant you have passed genes",
370
+                   "not in the fitness table."))
371
+    }
372
+    
373
+    indicesM <- as.vector(na.omit(match( drv, geneModule$Gene)))
374
+    indicesI <- as.vector(na.omit(sort(match( drv, geneNoInt$Gene))))
375
+    if(sort) {
376
+        indicesM <- sort(indicesM)
377
+    }
362 378
     return(c(
363 379
         geneModule$GeneNumID[indicesM],
364 380
         geneNoInt$GeneNumID[indicesI])
... ...
@@ -489,7 +505,7 @@ allFitnessEffects <- function(rT = NULL,
489 505
     }
490 506
 
491 507
     if(!is.null(drvNames)) {
492
-        drv <- getDrv(geneModule, geneNoInt, drvNames)
508
+        drv <- getGeneIDNum(geneModule, geneNoInt, drvNames)
493 509
     } else {
494 510
         drv <- geneModule$GeneNumID[-1]
495 511
     }
... ...
@@ -831,7 +847,15 @@ nr_oncoSimul.internal <- function(rFE,
831 847
                    "as created, for instance, with function",
832 848
                    "allFitnessEffects"))
833 849
     if(!is.null(initMutant)) {
834
-        initMutant <- getDrv(rFE$geneModule, initMutant)
850
+       if(length(grep(">", initMutant))) {
851
+            initMutant <- nice.vector.eo(initMutant, ">")
852
+        } else if(length(grep(",", initMutant))) {
853
+            initMutant <- nice.vector.eo(initMutant, ",")
854
+        }
855
+        initMutant <- getGeneIDNum(rFE$geneModule,
856
+                             rFE$long.geneNoInt,
857
+                                   initMutant,
858
+                                   FALSE)
835 859
     } else {
836 860
         initMutant <- vector(mode = "integer")
837 861
     }
... ...
@@ -1,3 +1,6 @@
1
+Changes in version 1.99.5 (2015-06-25):
2
+	- Fixed bug in initMutant, added tests, and vignette section.
3
+
1 4
 Changes in version 1.99.4 (2015-06-22):
2 5
 	- Tried randutils, from O'Neill. Won't work with gcc-4.6.
3 6
 	- bool issue in Windows/gcc-4.6.
... ...
@@ -267,10 +267,12 @@ to be detected.  For \code{oncoSimulSample} this can be a vector.
267 267
 %% \item{seed}{The seed to use for the C++ random number generator. If not
268 268
 %%   passed explicitly (the default) then chosen from R.}
269 269
 
270
-\item{initMutant}{For v.2, a vector of the mutations of the initial
271
-  clone for the simulations. For v.1, the single mutation of the initial
272
-  clone for the simulations. The default (if you pass nothing) is to
273
-  start the simulation from the wildtype genotype with nothing mutated.}
270
+\item{initMutant}{For v.2, a string with the mutations of the initial
271
+  mutant, if any. This is the same format as for
272
+  \code{\link{evalGenotype}}. For v.1, the single mutation of the
273
+  initial clone for the simulations. The default (if you pass nothing)
274
+  is to start the simulation from the wildtype genotype with nothing
275
+  mutated.}
274 276
 
275 277
 
276 278
 \item{max.num.tries}{Only applies when \code{onlyCancer = TRUE}. What is
... ...
@@ -857,9 +857,8 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects,
857 857
     Genotypes[0] = createNewGenotype(wtGenotype(),
858 858
 				     initMutant,
859 859
 				     fitnessEffects,
860
-				     ran_gen); // FIXME: nr, here. What is a "wt
861
-					// genotype"? Does it have "0"
862
-					// mutated, or nothing. Nothing.
860
+				     ran_gen,
861
+				     false); 
863 862
     if(typeModel == TypeModel::beerenwinkel) {
864 863
       
865 864
       popParams[0].death = 1.0; //note same is in McFarland.
... ...
@@ -1251,7 +1250,8 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects,
1251 1250
 	newGenotype = createNewGenotype(Genotypes[nextMutant],
1252 1251
 					newMutations,
1253 1252
 					fitnessEffects,
1254
-					ran_gen);
1253
+					ran_gen,
1254
+					true);
1255 1255
 
1256 1256
 	// nr_change
1257 1257
 	// newGenotype = Genotypes[nextMutant];
... ...
@@ -517,9 +517,13 @@ std::map<int, std::string> mapGenesIntToNames(const fitnessEffectsAll& fe) {
517 517
 Genotype createNewGenotype(const Genotype& parent,
518 518
 			   const std::vector<int>& mutations,
519 519
 			   const fitnessEffectsAll& fe,
520
-			   std::mt19937& ran_gen
520
+			   std::mt19937& ran_gen,
521 521
 			   //randutils::mt19937_rng& ran_gen
522
-			   ) {
522
+			   bool random = true) {
523
+  // random: if multiple mutations, randomly shuffle the ordered ones?
524
+  // This is the way to go if chromothripsis, but not if we give an
525
+  // initial mutant
526
+  
523 527
   Genotype newGenot = parent;
524 528
   std::vector<int> tempOrder; // holder for multiple muts if order.
525 529
   bool sort_rest = false;
... ...
@@ -553,7 +557,9 @@ Genotype createNewGenotype(const Genotype& parent,
553 557
 
554 558
   // If there is order but multiple simultaneous mutations
555 559
   // (chromothripsis), we randomly insert them
556
-  if(tempOrder.size() > 1)
560
+
561
+  // FIXME: initMutant cannot use this!! we give the order!!!
562
+  if( (tempOrder.size() > 1) && random)
557 563
     shuffle(tempOrder.begin(), tempOrder.end(), ran_gen);
558 564
   // The new randutils engine:
559 565
   // if(tempOrder.size() > 1)
... ...
@@ -174,9 +174,9 @@ void obtainMutations(const Genotype& parent,
174 174
 Genotype createNewGenotype(const Genotype& parent,
175 175
 			   const std::vector<int>& mutations,
176 176
 			   const fitnessEffectsAll& fe,
177
-			   std::mt19937& ran_gen
177
+			   std::mt19937& ran_gen,
178 178
 			   //randutils::mt19937_rng& ran_gen
179
-			   );
179
+			   bool random);
180 180
 
181 181
 std::vector<double> evalGenotypeFitness(const Genotype& ge,
182 182
 					const fitnessEffectsAll& F);
183 183
new file mode 100644
... ...
@@ -0,0 +1,162 @@
1
+test_that("initMutant crashes",
2
+          {
3
+              o3 <- allFitnessEffects(orderEffects = c(
4
+                                          "M > D > F" = 0.99,
5
+                                          "D > M > F" = 0.2,
6
+                                          "D > M"     = 0.1,
7
+                                          "M > D"     = 0.9),
8
+                                      noIntGenes = c(0.01, 0.01),
9
+                                      geneToModule =
10
+                                          c("Root" = "Root",
11
+                                            "M" = "m",
12
+                                            "F" = "f",
13
+                                            "D" = "d") )
14
+              expect_error(oncoSimulIndiv(o3, model = "McFL",
15
+                      mu = 5e-5, finalTime = 500,
16
+                      detectionDrivers = 3,
17
+                      onlyCancer = FALSE,
18
+                      initSize = 1000,
19
+                      keepPhylog = TRUE
20
+                     , initMutant = c("b, a") ## also "a" and "b" separate
21
+                                          ))
22
+              expect_error(oncoSimulIndiv(o3, model = "McFL",
23
+                      mu = 5e-5, finalTime = 500,
24
+                      detectionDrivers = 3,
25
+                      onlyCancer = FALSE,
26
+                      initSize = 1000,
27
+                      keepPhylog = TRUE
28
+                     , initMutant = c("b", "a") ## also "a" and "b" separate
29
+                                          ))
30
+              expect_error(oncoSimulIndiv(o3, model = "McFL",
31
+                      mu = 5e-5, finalTime = 500,
32
+                      detectionDrivers = 3,
33
+                      onlyCancer = FALSE,
34
+                      initSize = 1000,
35
+                      keepPhylog = TRUE
36
+                     , initMutant = c("1", "2") ## also "a" and "b" separate
37
+                                          ))
38
+          })
39
+
40
+
41
+test_that("initMutant lexicog order",
42
+          {
43
+              o3 <- allFitnessEffects(orderEffects = c(
44
+                                          "M > D > F" = 0.99,
45
+                                          "D > M > F" = 0.2,
46
+                                          "D > M"     = 0.1,
47
+                                          "M > D"     = 0.9),
48
+                                      noIntGenes = c(0.01, 0.01),
49
+                                      geneToModule =
50
+                                          c("Root" = "Root",
51
+                                            "M" = "m",
52
+                                            "F" = "f",
53
+                                            "D" = "d") )
54
+              tmp <- oncoSimulIndiv(o3, model = "McFL",
55
+                      mu = 5e-5, finalTime = 500,
56
+                      detectionDrivers = 3,
57
+                      onlyCancer = FALSE,
58
+                      initSize = 1000,
59
+                      keepPhylog = TRUE
60
+                     , initMutant = c("d > m")
61
+                      )
62
+              cn <- colnames(igraph::get.adjacency(plotClonePhylog(tmp, N = 0,
63
+                                                                   returnGraph = TRUE),
64
+                                                   sparse = FALSE))
65
+              expect_true( "d, m_" %in% cn )
66
+              expect_true( "d, m, f_" %in% cn )
67
+              expect_false( "m, d_" %in% cn )
68
+              expect_false( "m, d, f_" %in% cn )
69
+          })
70
+
71
+
72
+test_that("initMutant lexicog order with noint",
73
+          {
74
+              o3 <- allFitnessEffects(orderEffects = c(
75
+                                          "M > D > F" = 0.99,
76
+                                          "D > M > F" = 0.2,
77
+                                          "D > M"     = 0.1,
78
+                                          "M > D"     = 0.9),
79
+                                      noIntGenes = c("u" = 0.01, "z" = 0.01),
80
+                                      geneToModule =
81
+                                          c("Root" = "Root",
82
+                                            "M" = "m",
83
+                                            "F" = "f",
84
+                                            "D" = "d") )
85
+              tmp <- oncoSimulIndiv(o3, model = "McFL",
86
+                      mu = 5e-5, finalTime = 500,
87
+                      detectionDrivers = 3,
88
+                      onlyCancer = FALSE,
89
+                      initSize = 1000,
90
+                      keepPhylog = TRUE
91
+                     , initMutant = c("d > m > z")
92
+                      )
93
+              cn <- colnames(igraph::get.adjacency(plotClonePhylog(tmp, N = 0,
94
+                                                                   returnGraph = TRUE),
95
+                                                   sparse = FALSE))
96
+              expect_true( "d, m_z" %in% cn )
97
+              expect_true( "d, m, f_z" %in% cn )
98
+              expect_false( "m, d_" %in% cn )
99
+              expect_false( "m, d, f_" %in% cn )
100
+          })
101
+
102
+
103
+test_that("initMutant non lexicog order",
104
+          {
105
+              o3 <- allFitnessEffects(orderEffects = c(
106
+                                          "M > D > F" = 0.99,
107
+                                          "D > M > F" = 0.2,
108
+                                          "D > M"     = 0.1,
109
+                                          "M > D"     = 0.9),
110
+                                      noIntGenes = c("u" = 0.01, "z" = 0.01),
111
+                                      geneToModule =
112
+                                          c("Root" = "Root",
113
+                                            "M" = "m",
114
+                                            "F" = "f",
115
+                                            "D" = "d") )
116
+              tmp <- oncoSimulIndiv(o3, model = "McFL",
117
+                      mu = 5e-5, finalTime = 500,
118
+                      detectionDrivers = 3,
119
+                      onlyCancer = FALSE,
120
+                      initSize = 1000,
121
+                      keepPhylog = TRUE
122
+                     , initMutant = c("m > d")
123
+                      )
124
+              cn <- colnames(igraph::get.adjacency(plotClonePhylog(tmp, N = 0,
125
+                                                                   returnGraph = TRUE),
126
+                                                   sparse = FALSE))
127
+              expect_false( "d, m_" %in% cn )
128
+              expect_false( "d, m, f_" %in% cn )
129
+              expect_true( "m, d_" %in% cn )
130
+              expect_true( "m, d, f_" %in% cn )
131
+          })
132
+
133
+
134
+test_that("initMutant non lexicog order",
135
+          {
136
+              o3 <- allFitnessEffects(orderEffects = c(
137
+                                          "M > D > F" = 0.99,
138
+                                          "D > M > F" = 0.2,
139
+                                          "D > M"     = 0.1,
140
+                                          "M > D"     = 0.9),
141
+                                      noIntGenes = c("u" = 0.01, "z" = 0.01),
142
+                                      geneToModule =
143
+                                          c("Root" = "Root",
144
+                                            "M" = "m",
145
+                                            "F" = "f",
146
+                                            "D" = "d") )
147
+              tmp <- oncoSimulIndiv(o3, model = "McFL",
148
+                      mu = 5e-5, finalTime = 500,
149
+                      detectionDrivers = 3,
150
+                      onlyCancer = FALSE,
151
+                      initSize = 1000,
152
+                      keepPhylog = TRUE
153
+                     , initMutant = c("m > u > d")
154
+                      )
155
+              cn <- colnames(igraph::get.adjacency(plotClonePhylog(tmp, N = 0,
156
+                                                                   returnGraph = TRUE),
157
+                                                   sparse = FALSE))
158
+              expect_false( "d, m_" %in% cn )
159
+              expect_false( "d, m, f_" %in% cn )
160
+              expect_true( "m, d_u" %in% cn )
161
+              expect_true( "m, d, f_u" %in% cn )
162
+          })
... ...
@@ -57,6 +57,9 @@ BiocStyle::latex()
57 57
 %%}
58 58
 
59 59
 
60
+%% FIXME: the homozigos, etc.
61
+
62
+
60 63
 \bioctitle[\textit{OncoSimulR: genetic simulation with arbitrary
61 64
   epistasis}]{OncoSimulR: forward genetic simulation in asexual
62 65
   populations with arbitrary epistatic interactions and a focus on modeling
... ...
@@ -79,8 +82,12 @@ BiocStyle::latex()
79 82
 %%     \gitAbbrevHash)}}
80 83
 
81 84
 
85
+ %% I use x.y.z and gitinfo does not deal with this well in gitVtags et al.
86
+%% \date{\gitAuthorDate\ {\footnotesize (Version:\gitVtags, Rev: \gitAbbrevHash)}}
87
+
82 88
 \date{\gitAuthorDate\ {\footnotesize (Rev: \gitAbbrevHash)}}
83
- 
89
+
90
+
84 91
 \begin{document}
85 92
 \maketitle
86 93
 
... ...
@@ -138,10 +145,11 @@ core of the code is implemented in C++, providing for fast execution.
138 145
 Finally, to help with simulation studies, code to simulate random graphs
139 146
 of the kind often seen in CBN, OTs, etc, is also available.
140 147
 
148
+\subsection{Key features of OncoSimulR}\label{key}
141 149
 
142
-Therefore, OncoSimulR is now a very general package for forward genetic
143
-simulation, with applicability well beyond tumor progression. This is a
144
-summary of some of the key features:
150
+As mentioned above, OncoSimulR is now a very general package for forward
151
+genetic simulation, with applicability well beyond tumor progression. This
152
+is a summary of some of the key features:
145 153
 
146 154
 
147 155
 \begin{itemize}
... ...
@@ -177,12 +185,16 @@ summary of some of the key features:
177 185
     \item Code in C++ is available (though not yet callable from R) for
178 186
       using several other models, including the one from Beerenwinkel and
179 187
       collaborators \cite{Beerenwinkel2007b}.
188
+      
180 189
     \item You can use very large numbers of genes (e.g., see an example of
181 190
       50000 in section \ref{mcf50070} ).
182 191
       
183 192
     \item Simulations are generally very fast as I use C++ to implement
184 193
       the BNB algorithm.
185 194
       
195
+    \item You can obtain the true sequence of events and the phylogenetic
196
+      relationships between clones.
197
+      
186 198
 \end{itemize}
187 199
 
188 200
 
... ...
@@ -244,11 +256,32 @@ need that for your usual interactive work).
244 256
 
245 257
 <<results="hide">>=
246 258
 library(OncoSimulR)
247
-packageVersion("OncoSimulR")
248 259
 library(graph)
249 260
 library(igraph)
250 261
 @ 
251 262
 
263
+To be explicit, what version are we running?
264
+<<>>=
265
+packageVersion("OncoSimulR")
266
+@ 
267
+
268
+
269
+\subsection{A temporary note about versions}\label{versions}
270
+
271
+In this vignette and the documentation I often refer to version 1 (v.1)
272
+and version 2 of OncoSimulR. Version 1 is the version available up to, and
273
+including, BioConductor v.\ 3.1. Version 2 of OncoSimulR is available for
274
+the current BioConductor development branch, 3.2. If you look at the
275
+package version, however, it currently shows as 1.99.x (where x should be
276
+a number $\ge 4$). That is because of the versioning scheme of
277
+BioConductor. This will become 2.0 in the next release of BioConductor.
278
+
279
+Summary: if you are using the current development version of BioConductor,
280
+or you grab the sources from github
281
+(\Burl{https://github.com/rdiaz02/OncoSimul}) you are using what we call
282
+version 2. If you see a version in the package that says ``1.99.x'', where
283
+``x'' is any number, you are too.
284
+
252 285
 
253 286
 
254 287
 \section{Specifying fitness effects}\label{specfit}
... ...
@@ -1875,6 +1908,50 @@ evalGenotype(randomGenotype(fea), fea, echo = TRUE, verbose = TRUE)
1875 1908
 
1876 1909
 @ 
1877 1910
 
1911
+\subsection{Homozygosity, heterozygosity, oncogenes, tumor suppressors}\label{oncog}
1912
+
1913
+We are using what is conceptually a single linear chromosome. However, you
1914
+can use it to model scenarios where the numbers of copies affected matter,
1915
+by properly duplicating the genes. 
1916
+
1917
+Suppose we have a tumor suppressor gene, G, with two copies, one from Mom
1918
+and one from Dad. We can have a table like:
1919
+
1920
+
1921
+\begin{tabular} {c c c}
1922
+  $G_M$ & $G_D$ & Fitness \\
1923
+  \hline
1924
+  wt&wt& 1 \\
1925
+  wt&M& 1 \\
1926
+  M&wt& 1\\
1927
+  M&M& $(1 + s)$\\
1928
+  \hline
1929
+\end{tabular}
1930
+
1931
+where $s > 0$, meaning that you need two hits, one in each copy, to
1932
+trigger the clonal expansion.
1933
+
1934
+
1935
+What about oncogenes? A simple model is that one single hit leads to
1936
+clonal expansion and additional hits lead to no additional changes, as in
1937
+this table for gene O, where again the M or D subscript denotes the copy
1938
+from Mom or from Dad:
1939
+
1940
+\begin{tabular} {c c c}
1941
+  $O_M$ & $O_D$ & Fitness \\
1942
+  \hline
1943
+  wt&wt& 1 \\
1944
+  wt&M&  $(1 + s)$\\
1945
+  M&wt& $(1 + s)$\\
1946
+  M&M& $(1 + s)$\\
1947
+  \hline
1948
+\end{tabular}
1949
+
1950
+If you have multiple copies you can proceed similarly. As you can see,
1951
+these are nothing but special cases of synthetic mortality (\ref{sl}),
1952
+synthetic viability (\ref{sv}) and epistasis (\ref{epi}).
1953
+
1954
+
1878 1955
 \section{Specifying fitness effects: some examples from the literature}\label{litex}
1879 1956
 \subsection{Bauer et al}\label{bauer}
1880 1957
 
... ...
@@ -3227,6 +3304,41 @@ thus in the output you can have two columns with both genes mutated.
3227 3304
 %% more meaningful names.
3228 3305
 
3229 3306
 
3307
+\subsection{Can I start the simulation from a specific mutant?}\label{initmut}
3308
+
3309
+You bet. In v.1 you can only give the initial mutant as one with a single
3310
+mutated gene. In version 2, however, you can specify the genotype for the
3311
+initial mutant with the same flexibility as in
3312
+\Rfunction{evalGenotype}. Here we show a couple of examples (we use the
3313
+representation of the phylogeny, discussed in section \ref{phylog} of the
3314
+clones so that you can see which clones appear, and from which).
3315
+
3316
+
3317
+<<fig.height=6>>=
3318
+
3319
+o3init <- allFitnessEffects(orderEffects = c(
3320
+                            "M > D > F" = 0.99,
3321
+                            "D > M > F" = 0.2,
3322
+                            "D > M"     = 0.1,
3323
+                            "M > D"     = 0.9),
3324
+                        noIntGenes = c("u" = 0.01, "z" = 0.01),
3325
+                        geneToModule =
3326
+                            c("Root" = "Root",
3327
+                              "M" = "m",
3328
+                              "F" = "f",
3329
+                              "D" = "d") )
3330
+tmpI <- oncoSimulIndiv(o3init, model = "McFL",
3331
+                       mu = 5e-5, finalTime = 500,
3332
+                       detectionDrivers = 3,
3333
+                       onlyCancer = FALSE,
3334
+                       initSize = 1000,
3335
+                       keepPhylog = TRUE,
3336
+                       initMutant = c("m > u > d")
3337
+                      )
3338
+plotClonePhylog(tmpI, N = 0)
3339
+
3340
+@ 
3341
+
3230 3342
 
3231 3343
 \section{Showing the true phylogenetic relationships of clones}\label{phylog}
3232 3344
 
... ...
@@ -3258,7 +3370,12 @@ tmp <-  oncoSimulIndiv(examplesFitnessEffects[["o3"]],
3258 3370
 tmp
3259 3371
 @ 
3260 3372
 
3261
-We can plot the phylogenetic relationships of every clone ever created
3373
+We can plot the phylogenetic relationships\footnote{There are several
3374
+  packages in R devoted to phylogenetic inference and related issues. For
3375
+  instance, \CRANpkg{ape}. I have not used that infrastructure because of
3376
+  our very specific needs and circumstances; for instance, internal nodes
3377
+  are observed, we can have networks instead of trees, and we have no
3378
+  uncertainty about when events occurred.} of every clone ever created
3262 3379
 (with fitness larger than 0 ---clones without viability are never shown):
3263 3380
 
3264 3381
 <<>>=
... ...
@@ -3375,12 +3492,33 @@ key clones.
3375 3492
 %% plotClonePhylog(tmp, FALSE, FALSE, FALSE)
3376 3493
 %% @ 
3377 3494
 
3495
+
3496
+It is of course quite possible that, especially if we consider few genes,
3497
+our phylogeny will be a network, not a tree, as the same child node can
3498
+have multiple parents. You can play with this example, modified from one
3499
+we saw before (section \ref{mn1}):
3500
+
3501
+<<eval=FALSE>>=
3502
+op <- par(ask = TRUE)
3503
+while(TRUE) {
3504
+    tmp <- oncoSimulIndiv(smn1, model = "McFL",
3505
+                          mu = 5e-5, finalTime = 500,
3506
+                          detectionDrivers = 3,
3507
+                          onlyCancer = FALSE,
3508
+                          initSize = 1000, keepPhylog = TRUE)
3509
+    plotClonePhylog(tmp, N = 0)
3510
+}
3511
+par(op)
3512
+@ 
3513
+
3514
+
3378 3515
 \subsection{Phylogenies from multiple runs}\label{phylogmult}
3379 3516
 
3380 3517
 If you use \Rfunction{oncoSimulPop} you can store and plot the phylogenies
3381 3518
 of the different runs:
3382 3519
 
3383 3520
 <<>>=
3521
+
3384 3522
 oi <- allFitnessEffects(orderEffects =
3385 3523
                c("F > D" = -0.3, "D > F" = 0.4),
3386 3524
                noIntGenes = rexp(5, 10),
... ...
@@ -3397,10 +3535,13 @@ oiP1 <- oncoSimulPop(4, oi,
3397 3535
 @ 
3398 3536
 
3399 3537
 We will plot the first two:
3400
-<<>>=
3401
-par(mfrow = c(2, 1))
3538
+<<fig.height=9>>=
3539
+
3540
+op <- par(mar = rep(0, 4), mfrow = c(2, 1))
3402 3541
 plotClonePhylog(oiP1[[1]])
3403 3542
 plotClonePhylog(oiP1[[2]])
3543
+par(op)
3544
+
3404 3545
 @ 
3405 3546
 
3406 3547
 
... ...
@@ -1,15 +1,15 @@
1 1
 \usepackage[%
2
-		shash={7bd55ca},
3
-		lhash={7bd55caf3447abdf6298a7264394e745f71cbc98},
2
+		shash={4be528e},
3
+		lhash={4be528e9d8681d84f611c60f30950975ab76155c},
4 4
 		authname={ramon diaz-uriarte (at Bufo)},
5 5
 		authemail={rdiaz02@gmail.com},
6
-		authsdate={2015-06-22},
7
-		authidate={2015-06-22 19:20:10 +0200},
8
-		authudate={1434993610},
6
+		authsdate={2015-06-24},
7
+		authidate={2015-06-24 09:36:48 +0200},
8
+		authudate={1435131408},
9 9
 		commname={ramon diaz-uriarte (at Bufo)},
10 10
 		commemail={rdiaz02@gmail.com},
11
-		commsdate={2015-06-22},
12
-		commidate={2015-06-22 19:20:10 +0200},
13
-		commudate={1434993610},
11
+		commsdate={2015-06-24},
12
+		commidate={2015-06-24 09:36:48 +0200},
13
+		commudate={1435131408},
14 14
 		refnames={ (HEAD, master)}
15 15
 	]{gitsetinfo}
16 16
\ No newline at end of file