Browse code

more on robust tests

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

Ramon Diaz-Uriarte authored on 01/10/2015 12:49:30
Showing 7 changed files

... ...
@@ -2,7 +2,7 @@ Package: OncoSimulR
2 2
 Type: Package
3 3
 Title: Forward Genetic Simulation of Cancer Progresion with Epistasis 
4 4
 Version: 1.99.8
5
-Date: 2015-10-01
5
+Date: 2015-30-01
6 6
 Author: Ramon Diaz-Uriarte. 
7 7
 Maintainer: Ramon Diaz-Uriarte <rdiaz02@gmail.com>
8 8
 Description: Functions for forward population genetic simulation in
... ...
@@ -648,8 +648,8 @@ void addToPhylog(PhylogName& phylog,
648 648
 
649 649
 static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects,
650 650
 			const double& initSize,
651
-		     const double& K,
652
-		     const double& alpha,
651
+			const double& K,
652
+			const double& alpha,
653 653
 		     const double& genTime,
654 654
 		     const TypeModel typeModel,
655 655
 		     const int& mutatorGenotype,
... ...
@@ -665,28 +665,28 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects,
665 665
 		     const int& detectionDrivers,
666 666
 		     const double& minDetectDrvCloneSz,
667 667
 		     const double& extraTime,
668
-		     const int& verbosity,
669
-		     double& totPopSize,
670
-		     double& e1,
671
-		     double& n_0,
672
-		     double& n_1,
673
-		     double& ratioForce,
674
-		     double& currentTime,
675
-		     int& speciesFS,
676
-		     int& outNS_i,
677
-		     int& iter,
678
-		     std::vector<Genotype>& genot_out,
679
-		     std::vector<double>& popSizes_out,
680
-		     std::vector<int>& index_out,
681
-		     std::vector<double>& time_out,
682
-		     std::vector<double>& sampleTotPopSize,
683
-		     std::vector<double>& sampleLargestPopSize,
684
-		     std::vector<int>& sampleMaxNDr,
685
-		     std::vector<int>& sampleNDrLargestPop,
686
-		     bool& reachDetection,
668
+			const int& verbosity,
669
+			double& totPopSize,
670
+			double& e1,
671
+			double& n_0,
672
+			double& n_1,
673
+			double& ratioForce,
674
+			double& currentTime,
675
+			int& speciesFS,
676
+			int& outNS_i,
677
+			int& iter,
678
+			std::vector<Genotype>& genot_out,
679
+			std::vector<double>& popSizes_out,
680
+			std::vector<int>& index_out,
681
+			std::vector<double>& time_out,
682
+			std::vector<double>& sampleTotPopSize,
683
+			std::vector<double>& sampleLargestPopSize,
684
+			std::vector<int>& sampleMaxNDr,
685
+			std::vector<int>& sampleNDrLargestPop,
686
+			bool& reachDetection,
687 687
 			std::mt19937& ran_gen,
688 688
 			// randutils::mt19937_rng& ran_gen,
689
-		     double& runningWallTime,
689
+			double& runningWallTime,
690 690
 			bool& hittedWallTime,
691 691
 			const std::map<int, std::string>& intName,
692 692
 			const fitness_as_genes& genesInFitness,
... ...
@@ -1287,6 +1287,8 @@ static void nr_innerBNB(const fitnessEffectsAll& fitnessEffects,
1287 1287
 		     adjust_fitness_B, adjust_fitness_MF);
1288 1288
 	
1289 1289
 	  if(tmpParam.birth > 0.0) {
1290
+	    // if(keepMutationTimes)
1291
+	    //   update_mutation_freqs(newMutation, currentTime, mutation_freq_at);
1290 1292
 	    //FIXME: phylog
1291 1293
 	    if(keepPhylog)
1292 1294
 	      addToPhylog(phylog, Genotypes[nextMutant], newGenotype, currentTime,
... ...
@@ -164,7 +164,7 @@ test_that("initMutant non lexicog order",
164 164
               expect_true( "m, d, f_u" %in% cn )
165 165
           })
166 166
 
167
-
167
+## FIXME: we could use stronger test: we will never see M > D
168 168
 test_that("initMutant with oncoSimulSample", {
169 169
     o3init <- allFitnessEffects(orderEffects = c(
170 170
                             "M > D > F" = 0.99,
... ...
@@ -187,7 +187,7 @@ test_that("initMutant with oncoSimulSample", {
187 187
                         mu = 5e-5, finalTime = 5000,
188 188
                         detectionDrivers = 2,
189 189
                         onlyCancer = TRUE,
190
-                        initSize = 10,
190
+                        initSize = 500,
191 191
                         initMutant = c("z > d"),
192 192
                         thresholdWhole = 1 ## check presence of initMutant
193 193
                         )
... ...
@@ -202,52 +202,56 @@ test_that("initMutant with oncoSimulSample", {
202 202
                       as.character(ossI$popSummary$OccurringDrivers)), 1:4)
203 203
 })
204 204
 
205
-## This fails less than 1 in /10000. Handle reliably
206
-## test_that("initMutant with oncoSimulSample, 2", {
207
-##     o3init <- allFitnessEffects(orderEffects = c(
208
-##                             "M > D > F" = 0.99,
209
-##                             "D > M > F" = 0.2,
210
-##                             "D > M"     = 0.1,
211
-##                             "M > D"     = 0.9,
212
-##                             "M > A"     = 0.25),
213
-##                         noIntGenes = c("u" = 0.01, 
214
-##                                        "v" = 0.01,
215
-##                                        "w" = 0.001,
216
-##                                        "x" = 0.0001,
217
-##                                        "y" = -0.0001,
218
-##                                        "z" = -0.001),
219
-##                         geneToModule =
220
-##                             c("Root" = "Root",
221
-##                               "A" = "a",
222
-##                               "M" = "m",
223
-##                               "F" = "f",
224
-##                               "D" = "d") )
225
-##     ossI <- oncoSimulSample(4, 
226
-##                         o3init, model = "Exp",
227
-##                         mu = 5e-5, finalTime = 5000,
228
-##                         detectionDrivers = 3,
229
-##                         onlyCancer = TRUE,
230
-##                         initSize = 10,
231
-##                         initMutant = c("z > a"),
232
-##                         thresholdWhole = 1 ## check presence of initMutant
233
-##                         )
234
-##     ssp <- ossI$popSample
235
-##     expect_equal(ssp[, c("a", "z")],
236
-##                  matrix(1, nrow = 4, ncol = 2,
237
-##                         dimnames = list(NULL, c("a", "z"))))
238
-##     expect_false(sum(ssp) == prod(dim(ssp))) ## we don't just have all of
239
-##                                              ## them, which would turn the
240
-##                                              ## previous into irrelevant
241
-##     expect_equal(grep("a",
242
-##                       as.character(ossI$popSummary$OccurringDrivers)), 1:4)
243
-## })
205
+
206
+test_that("initMutant with oncoSimulSample, 2", {
207
+    o3init <- allFitnessEffects(orderEffects = c(
208
+                            "M > D > F" = 0.99,
209
+                            "D > M > F" = 0.2,
210
+                            "D > M"     = 0.1,
211
+                            "M > D"     = 0.9,
212
+                            "M > A"     = 0.25,
213
+                            "A > H"     = 0.2,
214
+                            "A > G"     = 0.3),
215
+                        noIntGenes = c("u" = 0.1, 
216
+                                       "v" = 0.2,
217
+                                       "w" = 0.001,
218
+                                       "x" = 0.0001,
219
+                                       "y" = -0.0001,
220
+                                       "z" = -0.001),
221
+                        geneToModule =
222
+                            c("Root" = "Root",
223
+                              "A" = "a",
224
+                              "M" = "m",
225
+                              "F" = "f",
226
+                              "D" = "d",
227
+                              "H" = "h",
228
+                              "G" = "g") )
229
+    ossI <- oncoSimulSample(4, 
230
+                        o3init, model = "Exp",
231
+                        mu = 5e-5, finalTime = 5000,
232
+                        detectionDrivers = 3,
233
+                        onlyCancer = TRUE,
234
+                        initSize = 500,
235
+                        initMutant = c("z > a"),
236
+                        thresholdWhole = 1 ## check presence of initMutant
237
+                        )
238
+    ssp <- ossI$popSample
239
+    expect_equal(ssp[, c("a", "z")],
240
+                 matrix(1, nrow = 4, ncol = 2,
241
+                        dimnames = list(NULL, c("a", "z"))))
242
+    expect_false(sum(ssp) == prod(dim(ssp))) ## we don't just have all of
243
+                                             ## them, which would turn the
244
+                                             ## previous into irrelevant
245
+    expect_equal(grep("a",
246
+                      as.character(ossI$popSummary$OccurringDrivers)), 1:4)
247
+})
244 248
 
245 249
 
246 250
 test_that("initMutant with oncoSimulPop", {
247 251
     o3init <- allFitnessEffects(orderEffects = c(
248 252
                             "M > D > F" = 0.99,
249 253
                             "D > M > F" = 0.2,
250
-                            "D > M"     = 0.1,
254
+                            "D > M"     = 0.2,
251 255
                             "M > D"     = 0.9),
252 256
                         noIntGenes = c("u" = 0.01, 
253 257
                                        "v" = 0.01,
... ...
@@ -262,11 +266,11 @@ test_that("initMutant with oncoSimulPop", {
262 266
                               "D" = "d") )
263 267
     ospI <- oncoSimulPop(4, 
264 268
                         o3init, model = "Exp",
265
-                        mu = 5e-5, finalTime = 1000,
269
+                        mu = 5e-5, finalTime = 5000,
266 270
                         detectionDrivers = 3,
267 271
                         onlyCancer = TRUE,
268 272
                         keepPhylog = TRUE,
269
-                        initSize = 10,
273
+                        initSize = 500,
270 274
                         initMutant = c("d > m > y"),
271 275
                         mc.cores = 2
272 276
                         )
... ...
@@ -302,7 +306,7 @@ test_that("initMutant with oncoSimulPop, 2", {
302 306
                             "D > M > F" = 0.2,
303 307
                             "D > M"     = 0.1,
304 308
                             "M > D"     = 0.9),
305
-                        noIntGenes = c("u" = 0.01, 
309
+                            noIntGenes = c("u" = 0.01, 
306 310
                                        "v" = 0.01,
307 311
                                        "w" = 0.001,
308 312
                                        "x" = 0.0001,
... ...
@@ -319,7 +323,7 @@ test_that("initMutant with oncoSimulPop, 2", {
319 323
                         detectionDrivers = 4, ## yes, reach end
320 324
                         onlyCancer = FALSE,
321 325
                         keepPhylog = TRUE,
322
-                        initSize = 10,
326
+                        initSize = 100,
323 327
                         initMutant = c("m > v > d"),
324 328
                         mc.cores = 2
325 329
                         )
... ...
@@ -164,7 +164,7 @@ test_that("exercising oncoSimulSample, new format", {
164 164
 test_that("check error unknown timeSample", {
165 165
     data(examplePosets)
166 166
     p701 <- examplePosets[["p701"]]
167
-    r1 <- oncoSimulIndiv(p701, onlyCancer = TRUE)
167
+    r1 <- oncoSimulIndiv(p701, onlyCancer = TRUE, max.num.tries = 5000)
168 168
     expect_error(samplePop(r1, timeSample = "uniformo"), 
169 169
                  "Unknown timeSample option")
170 170
     expect_error(samplePop(r1, timeSample = "uni"), 
... ...
@@ -182,7 +182,7 @@ test_that("check error unknown timeSample", {
182 182
 test_that("check error unknown typeSample", {
183 183
     data(examplePosets)
184 184
     p701 <- examplePosets[["p701"]]
185
-    r1 <- oncoSimulIndiv(p701, onlyCancer = TRUE)
185
+    r1 <- oncoSimulIndiv(p701, onlyCancer = TRUE, max.num.tries = 5000)
186 186
     expect_error(samplePop(r1, typeSample = "uniformo"), 
187 187
                  "Unknown typeSample option")
188 188
     expect_error(samplePop(r1, typeSample = "uni"), 
... ...
@@ -6,7 +6,7 @@ nindiv <- 4
6 6
 
7 7
 
8 8
 test_that("oncoSimulSample success with large num tries", {
9
-    p1 <- oncoSimulSample(nindiv, p701, max.num.tries = 200 * nindiv,
9
+    p1 <- oncoSimulSample(nindiv, p701, max.num.tries = 5000 * nindiv,
10 10
                           onlyCancer = TRUE)
11 11
     expect_true(p1$probCancer < 1)
12 12
     expect_true(p1$attemptsUsed > nindiv)
... ...
@@ -37,7 +37,7 @@ test_that("oncoSimulSample exits with minimal num tries", {
37 37
 
38 38
 test_that("oncoSimulSample exits with small num tries", {
39 39
     p6 <- oncoSimulSample(nindiv, p701,
40
-                          max.num.tries = nindiv + 4,
40
+                          max.num.tries = nindiv + 2,
41 41
                           onlyCancer = TRUE)
42 42
     expect_true(p6$HittedMaxTries)
43 43
     expect_true(is.na(p6$popSummary))
... ...
@@ -197,13 +197,13 @@ test_that("exercising the sampling code, v2 objects", {
197 197
                                             "F" = "f1, f2, f3",
198 198
                                             "D" = "d1, d2") )
199 199
               o1 <- oncoSimulIndiv(oi, detectionSize = 1e4,
200
-                                   onlyCancer = TRUE)
200
+                                   onlyCancer = TRUE,
201
+                                   max.num.tries = 5000)
201 202
               o4 <- oncoSimulPop(2,
202 203
                                  oi, 
203 204
                                  detectionSize = 1e4,
204
-                                 onlyCancer = TRUE)
205
-              ## many of them are generating warnings, because sampling
206
-              ## with pop size of 0. That is OK.
205
+                                 onlyCancer = TRUE,
206
+                                 max.num.tries = 5000)
207 207
               expect_message(samplePop(o1),
208 208
                              "Subjects by Genes matrix of 1 subjects and 10 genes")
209 209
               expect_message(samplePop(o1, typeSample = "single",
... ...
@@ -242,14 +242,14 @@ test_that("exercising the sampling code, v2 objects, more", {
242 242
                                 typeDep = "MN")
243 243
               cbn1 <- allFitnessEffects(cs)
244 244
               o1 <- oncoSimulIndiv(cbn1, detectionSize = 1e4,
245
-                                   onlyCancer = TRUE)
245
+                                   onlyCancer = TRUE,
246
+                                   max.num.tries = 5000)
246 247
               o4 <- oncoSimulPop(4,
247 248
                                  cbn1, 
248 249
                                  detectionSize = 1e4,
249 250
                                  onlyCancer = TRUE,
250
-                                 mc.cores = 2)
251
-              ## many of them are generating warnings, because sampling
252
-              ## with pop size of 0. That is OK.
251
+                                 mc.cores = 2,
252
+                                 max.num.tries = 5000)
253 253
               expect_message(samplePop(o1),
254 254
                              "Subjects by Genes matrix of 1 subjects and 6 genes")
255 255
               expect_message(samplePop(o1, typeSample = "single",
... ...
@@ -1,15 +1,15 @@
1 1
 \usepackage[%
2
-		shash={ea5bee4},
3
-		lhash={ea5bee4855766a04a04786475d269790a28c8373},
2
+		shash={d3b5a5a},
3
+		lhash={d3b5a5acc1dd65694d086183fbf8b7fd2919c025},
4 4
 		authname={ramon diaz-uriarte (at Bufo)},
5 5
 		authemail={rdiaz02@gmail.com},
6
-		authsdate={2015-09-27},
7
-		authidate={2015-09-27 14:25:22 +0200},
8
-		authudate={1443356722},
6
+		authsdate={2015-10-01},
7
+		authidate={2015-10-01 14:42:40 +0200},
8
+		authudate={1443703360},
9 9
 		commname={ramon diaz-uriarte (at Bufo)},
10 10
 		commemail={rdiaz02@gmail.com},
11
-		commsdate={2015-09-27},
12
-		commidate={2015-09-27 14:25:22 +0200},
13
-		commudate={1443356722},
11
+		commsdate={2015-10-01},
12
+		commidate={2015-10-01 14:42:40 +0200},
13
+		commudate={1443703360},
14 14
 		refnames={ (HEAD -> master)}
15 15
 	]{gitsetinfo}
16 16
\ No newline at end of file