Browse code

Started debugging - memory spike

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

Benilton Carvalho authored on 16/04/2010 16:02:49
Showing 3 changed files

... ...
@@ -513,5 +513,7 @@ function (which expects ff objects and supports parallel processing)
513 513
 2010-04-11 R. Scharpf committed version 1.5.48
514 514
 ** added a few .Rd files
515 515
 
516
+2010-04-16 B Carvalho committed version 1.5.49
517
+** cosmetics - looking for cause of memory spike
516 518
 
517 519
 
... ...
@@ -1,7 +1,7 @@
1 1
 Package: crlmm
2 2
 Type: Package
3 3
 Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for Affymetrix SNP 5.0 and 6.0 and Illumina arrays.
4
-Version: 1.5.48
4
+Version: 1.5.49
5 5
 Date: 2010-04-09
6 6
 Author: Rafael A Irizarry, Benilton S Carvalho <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>
7 7
 Maintainer: Benilton S Carvalho <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
... ...
@@ -349,7 +349,8 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
349 349
   regionInfo <- getVarInEnv("regionInfo")
350 350
   params <- getVarInEnv("params")
351 351
   
352
-  ##IF gender not provide, we predict
352
+  ## IF gender not provide, we predict
353
+  ## FIXME: XIndex may be greater than ocProbesets()
353 354
   if(is.null(gender)){
354 355
     if(verbose) message("Determining gender.")
355 356
     XMedian <- apply(log2(A[XIndex,, drop=FALSE])+log2(B[XIndex,, drop=FALSE]), 2, median)/2
... ...
@@ -446,16 +447,16 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
446 447
     names(data4reg) <- c("AA", "AB", "BB")
447 448
     regParams <- cbind(  coef(lm(AA~AB*BB, data=data4reg)),
448 449
                        c(coef(lm(AB~AA+BB, data=data4reg)), 0), 
449
-                       coef(lm(BB~AA*AB, data=data4reg)))
450
+                         coef(lm(BB~AA*AB, data=data4reg)))
450 451
     rownames(regParams) <- c("intercept", "X", "Y", "XY")
451 452
     rm(data4reg)
452 453
   
453 454
     minN <- 3
454 455
     newparams[["centers"]][newparams[["N"]] < minN] <- NA
455 456
     Index <- setdiff(which(rowSums(is.na(newparams[["centers"]]))==1), YIndex)
456
-    if(verbose) cat("Filling out empty centers")
457
+    if(verbose) message("Filling out empty centers", appendLF=FALSE)
457 458
     for(i in Index){
458
-      if(verbose) if(i%%10000==0)cat(".")
459
+      if(verbose) if(i%%10000==0) message(".", appendLF=FALSE)
459 460
       mu <- newparams[["centers"]][i, ]
460 461
       j <- which(is.na(mu))
461 462
       newparams[["centers"]][i, j] <- c(1, mu[-j], prod(mu[-j]))%*%regParams[, j]
... ...
@@ -472,7 +473,7 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
472 473
     newparams[["centers"]][is.na(newparams[["centers"]])] <- params[["centers"]][is.na(newparams[["centers"]])]
473 474
     if(verbose) cat("\n")
474 475
   
475
-    if(verbose) message("Calculating and standardizing size of shift.")
476
+    if(verbose) message("Calculating and standardizing size of shift... ", appendLF=FALSE)
476 477
     GG <- DD <- newparams[["centers"]] - params[["centers"]]
477 478
     DD <- sweep(DD, 2, colMeans(DD[autosomeIndex, ]))
478 479
     SS <- cov(DD[autosomeIndex, ])
... ...
@@ -491,12 +492,15 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
491 492
       dev=1/sqrt( (2*pi)^3*det(SS))*exp(-0.5*dev)
492 493
     }
493 494
   }
495
+  if (verbose) message("OK")
494 496
     
495 497
   ## BC: must keep SD
496 498
   params[-2] <- newparams[-2]
497
-  
498
-  rm(newparams);gc(verbose=FALSE)  
499
-  if(verbose) cat("Calling", NR, "SNPs... ")
499
+  rm(newparams)
500
+  gc(verbose=FALSE)  
501
+
502
+  if(verbose) message("Calling ", NR, " SNPs... ", appendLF=FALSE)
503
+
500 504
   ## ###################
501 505
   ## ## MOVE TO C#######
502 506