Browse code

update createscCoGAPSSets

Genevieve Stein-O'Brien authored on 22/03/2018 15:06:07
Showing 2 changed files

... ...
@@ -14,7 +14,7 @@
14 14
 #' data(SimpSim)
15 15
 #' createscCoGAPSSets(SimpSim.D, SimpSim.S, nSets=2, "example")
16 16
 #' @export
17
-createscCoGAPSSets <- function(D, S, nSets, simulationName,samplingRatio=NULL,path="")
17
+createscCoGAPSSets <- function(D, nSets, simulationName,samplingRatio=NULL,path="")
18 18
 {
19 19
     # check gene names
20 20
     if (length(unique(colnames(D))) != length(colnames(D)))
... ...
@@ -41,7 +41,10 @@ createscCoGAPSSets <- function(D, S, nSets, simulationName,samplingRatio=NULL,pa
41 41
 
42 42
         # partition data
43 43
         sampleD <- D[,cellset]
44
-        sampleS <- S[,cellset]
44
+        #log transform 
45
+        sampleD <- log2(sampleD+1)
46
+        # generate S
47
+        sampleS <- pmax(.1*sampleD, .1)
45 48
         save(sampleD, sampleS, file=paste0(path,simulationName, "_partition_", set,".RData"));
46 49
     }
47 50
     return(simulationName)
48 51
new file mode 100644
... ...
@@ -0,0 +1,28 @@
1
+#' Post Processing of Parallel Output
2
+#'
3
+#' @param AP.fixed output of parallel gapsMapRun calls with same FP
4
+#' @param setPs data.frame with rows giving fixed patterns for P used as input
5
+#' for gapsMapRun
6
+#' @return list of two data.frames containing the A matrix estimates or their
7
+#' corresponding standard deviations from output of parallel CoGAPS
8
+postFixed4SC <- function(AP.fixed, setAs)
9
+{
10
+    ASummary <- AP.fixed[[1]]$Amean
11
+
12
+
13
+    PSummary <- do.call(cbind,lapply(AP.fixed, function(x) x$Pmean))
14
+    Psd <- do.call(cbind,lapply(AP.fixed, function(x) x$Psd))
15
+
16
+    Pmax <- apply(PSummary,2,max)
17
+    Pneu <- sweep(PSummary,2,Pmax,FUN="/")
18
+    Aneu <- sweep(ASummary,1,Pmax,FUN="*")
19
+
20
+    X <- apply(Pneu,2,range)
21
+    Y <- apply(setPs,2,range)
22
+    colnames(X) <- colnames(Y)
23
+    if (all.equal(X,Y,tolerance=0.01) != TRUE)
24
+        warning("Patterns do not match fixed values.")
25
+
26
+    Ps4fixAs<-list("P"=Pneu,"Psd"=Psd)
27
+    return(Ps4fixAs)
28
+}