Browse code

fix function names

zhewa authored on 23/04/2019 19:42:38
Showing 9 changed files

... ...
@@ -38,7 +38,8 @@ Imports:
38 38
     SummarizedExperiment,
39 39
     MCMCprecision,
40 40
     ggrepel,
41
-    Rtsne
41
+    Rtsne,
42
+    S4Vectors
42 43
 Suggests:
43 44
     testthat,
44 45
     knitr,
... ...
@@ -77,40 +77,23 @@ exportMethods(perplexity)
77 77
 exportMethods(resList)
78 78
 exportMethods(runParams)
79 79
 exportMethods(sampleLabel)
80
+import(MAST, except = c(combine))
81
+import(RColorBrewer)
80 82
 import(Rcpp)
81 83
 import(RcppEigen)
84
+import(SummarizedExperiment, except = c(shift, rowRanges))
85
+import(data.table)
82 86
 import(foreach)
83
-import(ggplot2)
84 87
 import(grDevices)
85 88
 import(graphics)
86 89
 import(grid)
90
+import(gridExtra)
91
+import(gridExtra, except = c(combine))
87 92
 import(gtable)
88
-import(stats)
89
-import(umap)
90
-importFrom(MAST,FromMatrix)
91
-importFrom(MAST,summary)
92
-importFrom(MAST,zlm)
93
-importFrom(MCMCprecision,fit_dirichlet)
94
-importFrom(RColorBrewer,brewer.pal)
95
-importFrom(Rtsne,Rtsne)
96
-importFrom(S4Vectors,mcols)
97
-importFrom(SummarizedExperiment,assay)
98
-importFrom(SummarizedExperiment,assayNames)
99
-importFrom(SummarizedExperiment,colData)
100
-importFrom(data.table,as.data.table)
101
-importFrom(digest,digest)
102
-importFrom(doParallel,registerDoParallel)
93
+import(matrixStats, except = c(count))
94
+import(plyr)
95
+import(scales)
103 96
 importFrom(enrichR,enrichr)
104
-importFrom(ggrepel,geom_text_repel)
105
-importFrom(gridExtra,grid.arrange)
106
-importFrom(matrixStats,logSumExp)
107
-importFrom(methods,.hasSlot)
108
-importFrom(methods,is)
109
-importFrom(methods,new)
110
-importFrom(plyr,mapvalues)
111
-importFrom(reshape2,melt)
112
-importFrom(scales,dscale)
113
-importFrom(stringi,stri_list2matrix)
114 97
 useDynLib(celda,"_colSumByGroup")
115 98
 useDynLib(celda,"_colSumByGroupChange")
116 99
 useDynLib(celda,"_colSumByGroup_numeric")
... ...
@@ -397,7 +397,7 @@ setGeneric("celdaHeatmap",
397 397
 #'
398 398
 #'
399 399
 logLikelihood <- function(counts, model, ...) {
400
-    do.call(paste0("logLikelihood.", model),
400
+    do.call(paste0("logLikelihood", model),
401 401
         args = list(counts = counts, ...))
402 402
 }
403 403
 
... ...
@@ -461,7 +461,7 @@ setGeneric("perplexity",
461 461
 #' dim(celdaCGSim$counts)
462 462
 #' @export
463 463
 simulateCells <- function(model, ...) {
464
-    do.call(paste0("simulateCells.", model), args = list(...))
464
+    do.call(paste0("simulateCells", model), args = list(...))
465 465
 }
466 466
 
467 467
 
... ...
@@ -522,7 +522,7 @@ celda_C <- function(counts,
522 522
 #' celdaCSim <- simulateCells(model = "celda_C", K = 10)
523 523
 #' simCounts <- celdaCSim$counts
524 524
 #' @export
525
-simulateCells.celda_C <- function(model,
525
+simulateCellscelda_C <- function(model,
526 526
     S = 5,
527 527
     CRange = c(50, 100),
528 528
     NRange = c(500, 1000),
... ...
@@ -726,7 +726,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_C"),
726 726
 #' @seealso `celda_C()` for clustering cells
727 727
 #' @examples
728 728
 #' data(celdaCSim)
729
-#' loglik <- logLikelihood.celda_C(celdaCSim$counts,
729
+#' loglik <- logLikelihoodcelda_C(celdaCSim$counts,
730 730
 #'     sampleLabel = celdaCSim$sampleLabel,
731 731
 #'     z = celdaCSim$z,
732 732
 #'     K = celdaCSim$K,
... ...
@@ -741,7 +741,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_C"),
741 741
 #'     alpha = celdaCSim$alpha,
742 742
 #'     beta = celdaCSim$beta)
743 743
 #' @export
744
-logLikelihood.celda_C <- function(counts, sampleLabel, z, K, alpha, beta) {
744
+logLikelihoodcelda_C <- function(counts, sampleLabel, z, K, alpha, beta) {
745 745
 
746 746
     if (sum(z > K) > 0) {
747 747
         stop("An entry in z contains a value greater than the provided K.")
... ...
@@ -584,7 +584,7 @@ celda_CG <- function(counts,
584 584
 #' @examples
585 585
 #' celdaCGSim <- simulateCells(model = "celda_CG")
586 586
 #' @export
587
-simulateCells.celda_CG <- function(model,
587
+simulateCellscelda_CG <- function(model,
588 588
     S = 5,
589 589
     CRange = c(50, 100),
590 590
     NRange = c(500, 1000),
... ...
@@ -912,7 +912,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_CG"),
912 912
 #' @seealso `celda_CG()` for clustering features and cells
913 913
 #' @examples
914 914
 #' data(celdaCGSim)
915
-#' loglik <- logLikelihood.celda_CG(celdaCGSim$counts,
915
+#' loglik <- logLikelihoodcelda_CG(celdaCGSim$counts,
916 916
 #'     sampleLabel = celdaCGSim$sampleLabel,
917 917
 #'     z = celdaCGSim$z,
918 918
 #'     y = celdaCGSim$y,
... ...
@@ -935,7 +935,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_CG"),
935 935
 #'     gamma = celdaCGSim$gamma,
936 936
 #'     delta = celdaCGSim$delta)
937 937
 #' @export
938
-logLikelihood.celda_CG <- function(counts,
938
+logLikelihoodcelda_CG <- function(counts,
939 939
     sampleLabel,
940 940
     z,
941 941
     y,
... ...
@@ -454,7 +454,7 @@ celda_G <- function(counts,
454 454
 #' @examples
455 455
 #' celdaGSim <- simulateCells(model = "celda_G")
456 456
 #' @export
457
-simulateCells.celda_G <- function(model,
457
+simulateCellscelda_G <- function(model,
458 458
     C = 100,
459 459
     NRange = c(500, 1000),
460 460
     G = 100,
... ...
@@ -696,7 +696,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_G"),
696 696
 #' @seealso `celda_G()` for clustering features
697 697
 #' @examples
698 698
 #' data(celdaGSim)
699
-#' loglik <- logLikelihood.celda_G(celdaGSim$counts,
699
+#' loglik <- logLikelihoodcelda_G(celdaGSim$counts,
700 700
 #'     y = celdaGSim$y,
701 701
 #'     L = celdaGSim$L,
702 702
 #'     beta = celdaGSim$beta,
... ...
@@ -711,7 +711,7 @@ setMethod("factorizeMatrix", signature(celdaMod = "celda_G"),
711 711
 #'     delta = celdaGSim$delta,
712 712
 #'     gamma = celdaGSim$gamma)
713 713
 #' @export
714
-logLikelihood.celda_G <- function(counts, y, L, beta, delta, gamma) {
714
+logLikelihoodcelda_G <- function(counts, y, L, beta, delta, gamma) {
715 715
     if (sum(y > L) > 0) {
716 716
         stop("An entry in y contains a value greater than the provided L.")
717 717
     }
... ...
@@ -65,7 +65,7 @@ resamplePerplexity <- function(counts,
65 65
 #' plotGridSearchPerplexity(celdaCGGridSearchRes)
66 66
 #' @export
67 67
 plotGridSearchPerplexity <- function(celdaList, sep = 1) {
68
-    do.call(paste0("plotGridSearchPerplexity.",
68
+    do.call(paste0("plotGridSearchPerplexity",
69 69
         as.character(class(celdaList@resList[[1]]))),
70 70
         args = list(celdaList, sep))
71 71
 }
... ...
@@ -86,7 +86,7 @@ plotGridSearchPerplexity <- function(celdaList, sep = 1) {
86 86
 #' )
87 87
 #' plotGridSearchPerplexity(celdaCGGridSearchRes)
88 88
 #' @export
89
-plotGridSearchPerplexity.celda_CG <- function(celdaList, sep) {
89
+plotGridSearchPerplexitycelda_CG <- function(celdaList, sep) {
90 90
     if (!all(c("K", "L") %in% colnames(celdaList@runParams))) {
91 91
         stop("celdaList@runParams needs K and L columns.")
92 92
     }
... ...
@@ -158,7 +158,7 @@ plotGridSearchPerplexity.celda_CG <- function(celdaList, sep) {
158 158
 #' )
159 159
 #' plotGridSearchPerplexity(celdaCGGridSearchRes)
160 160
 #' @export
161
-plotGridSearchPerplexity.celda_C <- function(celdaList, sep) {
161
+plotGridSearchPerplexitycelda_C <- function(celdaList, sep) {
162 162
     if (!all(c("K") %in% colnames(celdaList@runParams))) {
163 163
         stop("runParams(celdaList) needs the column K.")
164 164
     }
... ...
@@ -207,7 +207,7 @@ plotGridSearchPerplexity.celda_C <- function(celdaList, sep) {
207 207
 #'   celdaCGGridSearchRes)
208 208
 #' plotGridSearchPerplexity(celdaCGGridSearchRes)
209 209
 #' @export
210
-plotGridSearchPerplexity.celda_G <- function(celdaList, sep) {
210
+plotGridSearchPerplexitycelda_G <- function(celdaList, sep) {
211 211
     if (!all(c("L") %in% colnames(celdaList@runParams))) {
212 212
         stop("celdaList@runParams needs the column L.")
213 213
     }
... ...
@@ -23,7 +23,7 @@
23 23
             ix <- z == i
24 24
             newZ <- z
25 25
             newZ[ix] <- ifelse(clustLabel@clusters$z == 2, i, K)
26
-            ll <- logLikelihood.celda_C(counts, s, newZ, K, alpha, beta)
26
+            ll <- logLikelihoodcelda_C(counts, s, newZ, K, alpha, beta)
27 27
 
28 28
             if (ll > bestLl) {
29 29
                 bestZ <- newZ
... ...
@@ -61,7 +61,7 @@
61 61
             ix <- y == i
62 62
             newY <- y
63 63
             newY[ix] <- ifelse(clustLabel@clusters$y == 2, i, L)
64
-            ll <- logLikelihood.celda_G(counts, newY, L, beta, delta, gamma)
64
+            ll <- logLikelihoodcelda_G(counts, newY, L, beta, delta, gamma)
65 65
 
66 66
             if (ll > bestLl) {
67 67
                 bestY <- newY
... ...
@@ -265,7 +265,7 @@ recursiveSplitCell <- function(counts,
265 265
                 overallZ <- tempModel@clusters$z
266 266
             } else {
267 267
                 overallZ <- tempSplit$z
268
-                ll <- logLikelihood.celda_CG(counts,
268
+                ll <- logLikelihoodcelda_CG(counts,
269 269
                     s,
270 270
                     overallZ,
271 271
                     tempModel@clusters$y,
... ...
@@ -353,7 +353,7 @@ recursiveSplitCell <- function(counts,
353 353
             reorder = reorder)
354 354
         currentK <- length(unique(modelInitial@clusters$z)) + 1
355 355
         overallZ <- modelInitial@clusters$z
356
-        ll <- logLikelihood.celda_C(counts, s, overallZ, currentK,
356
+        ll <- logLikelihoodcelda_C(counts, s, overallZ, currentK,
357 357
             alpha, beta)
358 358
         modelInitial@params$countChecksum <- countChecksum
359 359
         modelInitial@completeLogLik <- ll
... ...
@@ -391,7 +391,7 @@ recursiveSplitCell <- function(counts,
391 391
             }
392 392
 
393 393
             # Need to change below line to use decompose counts to save time
394
-            ll <- logLikelihood.celda_C(counts, s, overallZ, currentK,
394
+            ll <- logLikelihoodcelda_C(counts, s, overallZ, currentK,
395 395
                 alpha, beta)
396 396
             tempModel <- methods::new("celda_C",
397 397
                 clusters = list(z = overallZ),
... ...
@@ -471,7 +471,7 @@ recursiveSplitCell <- function(counts,
471 471
             } else {
472 472
                 overallZ <- tempSplit$z
473 473
                 ll <-
474
-                    logLikelihood.celda_C(counts, s, overallZ,
474
+                    logLikelihoodcelda_C(counts, s, overallZ,
475 475
                         currentK, alpha, beta)
476 476
                 tempModel <- methods::new("celda_C",
477 477
                     clusters = list(z = overallZ),
... ...
@@ -43,7 +43,6 @@ Uses MAST to find differentially expressed features for
43 43
 }
44 44
 \examples{
45 45
 data(celdaCGSim, celdaCGMod)
46
-library(SummarizedExperiment)
47 46
 clusterDiffexpRes = differentialExpression(celdaCGSim$counts,
48 47
     celdaCGMod, c1 = c(1, 2))
49 48
 }