Browse code

Add a max probability polyfunctional response calculation to the Respose function

update doc error.

add feature for probability of a degree of response or greater given response.

fix roxygen bug

fix export

whoops

add in_at_least

fix dep

fix dep ver num

rebuild docs. add convergence check for multiple compass models fit with different seeds

check fixes

minor fixes

gfinak authored on 03/05/2019 15:01:44 • Greg Finak committed on 12/05/2020 18:28:07
Showing 19 changed files

... ...
@@ -22,8 +22,8 @@ License: Artistic-2.0
22 22
 BugReports: https://github.com/RGLab/COMPASS/issues
23 23
 VignetteBuilder: knitr
24 24
 Depends:
25
-    R (>= 3.0.3)
26
-LinkingTo: Rcpp (>= 0.11.0)
25
+    R  (>= 3.0.3)
26
+LinkingTo: Rcpp  (>= 0.11.0)
27 27
 Maintainer: Greg Finak <[email protected]>
28 28
 Imports:
29 29
     methods,
... ...
@@ -45,7 +45,8 @@ Imports:
45 45
     tidyr,
46 46
     rlang,
47 47
     BiocStyle,
48
-    rmarkdown
48
+    rmarkdown,
49
+    foreach
49 50
 Suggests:
50 51
     flowWorkspace (>= 3.33.1),
51 52
     flowCore,
... ...
@@ -54,9 +55,11 @@ Suggests:
54 55
     testthat,
55 56
     devtools,
56 57
     flowWorkspaceData,
57
-    ggplot2
58
+    ggplot2,
59
+    doMC, 
60
+    progress 
58 61
 LazyLoad: yes
59 62
 LazyData: yes
60 63
 biocViews: ImmunoOncology, FlowCytometry
61 64
 Encoding: UTF-8
62
-RoxygenNote: 6.1.1
65
+RoxygenNote: 7.1.0
... ...
@@ -45,6 +45,7 @@ export(SimpleCOMPASS)
45 45
 export(TotalCellCounts)
46 46
 export(UniqueCombinations)
47 47
 export(categories)
48
+export(checkCOMPASSConvergence)
48 49
 export(getCounts)
49 50
 export(markers)
50 51
 export(metadata)
... ...
@@ -58,6 +59,7 @@ export(shinyCOMPASSDeps)
58 59
 export(translate_marker_names)
59 60
 export(transpose_list)
60 61
 import(data.table)
62
+import(foreach)
61 63
 import(grid)
62 64
 import(magrittr)
63 65
 import(methods)
... ...
@@ -113,4 +115,6 @@ importFrom(utils,globalVariables)
113 115
 importFrom(utils,head)
114 116
 importFrom(utils,installed.packages)
115 117
 importFrom(utils,sessionInfo)
118
+importFrom(utils,setTxtProgressBar)
119
+importFrom(utils,txtProgressBar)
116 120
 useDynLib(COMPASS, .registration=TRUE)
... ...
@@ -269,8 +269,8 @@ COMPASSContainerFromGatingSet<-function(gs = NULL, node = NULL, filter.fun = NUL
269 269
     expr <- do.call(c,strsplit(as.character(expr),"\\|"))
270 270
 
271 271
     ##validity check on the parent children relationship
272
-    children.ids <- sapply(full.child.nodes, flowWorkspace:::.getNodeInd, obj = gs[[1]], USE.NAMES = FALSE)
273
-    map.ids <- sapply(expr, flowWorkspace:::.getNodeInd, obj = gs[[1]], USE.NAMES = FALSE)
272
+    children.ids <- sapply(full.child.nodes, flowWorkspace::.getNodeInd, obj = gs[[1]], USE.NAMES = FALSE)
273
+    map.ids <- sapply(expr, flowWorkspace::.getNodeInd, obj = gs[[1]], USE.NAMES = FALSE)
274 274
     ind <- !map.ids %in% children.ids
275 275
     if(any(ind))
276 276
       stop(paste(expr[ind], collapse = "|"), " are not the children node of ", unique.node)
... ...
@@ -3,6 +3,9 @@
3 3
 #' @param x  a \code{COMPASSResult} object.
4 4
 #' @param markers a \code{vector} of marker names.
5 5
 #' @param degree the \code{numeric} degree of functionality to test.
6
+#' @param max.prob \code{logical} Use the max probability rather than the average across subsets. Defaults to FALSE.
7
+#' @param at_least_n \code{logical} response of degree x or greater with at_least_n subsets responding.
8
+
6 9
 #' @description
7 10
 #' Compute a response probability based on the selected markers, evaluating the probability
8 11
 #' that a subject exhibits a response of size \code{degree} or greater.
... ...
@@ -11,17 +14,17 @@
11 14
 #' @details
12 15
 #' The response is computed from the sampled Gamma matrix, subsetting on the selected markers, and
13 16
 #' @return  A \code{vector} of response probabilities for each subject.
14
-#' @export
15
-#'
16 17
 #' @examples
18
+#'
17 19
 #' Response(CR, markers = c("M1","M2","M3"), degree = 2)
18
-Response <- function(x, markers, degree){
20
+#' @export
21
+Response <- function(x, markers, degree, max.prob, at_least_n){
19 22
   UseMethod("Response")
20 23
 }
21 24
 
22 25
 ##' @rdname Response
23 26
 ##' @export
24
-Response.COMPASSResult <- function(x, markers = NULL, degree = 1) {
27
+Response.COMPASSResult <- function(x, markers = NULL, degree = 1, max.prob = FALSE, at_least_n = NULL) {
25 28
   ## we drop the last column as it is the 'NULL' category
26 29
   if (is.null(markers)) {
27 30
     markers <- markers(x)
... ...
@@ -33,6 +36,7 @@ Response.COMPASSResult <- function(x, markers = NULL, degree = 1) {
33 36
       stop("Invalid marker names")
34 37
     }
35 38
     message("Computing the probability of response of degree >= ",degree, " from markers: ", paste(markers, collapse = ", "))
39
+    if(!is.null(at_least_n)){message("in at least ",at_least_n," subsets.")}
36 40
     new_categories = unique(categories(x, FALSE)[, markers, drop = FALSE])
37 41
     all_categories = categories(x, FALSE)[, markers, drop = FALSE]
38 42
     suppressWarnings({dmat = as.matrix(pdist(new_categories, all_categories))})
... ...
@@ -43,24 +47,39 @@ Response.COMPASSResult <- function(x, markers = NULL, degree = 1) {
43 47
     }
44 48
     new_mean_gamma = apply(cat_indices, 2, function(i)
45 49
       apply(Gamma(x)[, i, ], 1, mean))
50
+    new_gamma <- Gamma(x)[,cat_indices,]
46 51
     new_categories = cbind(new_categories, Counts = rowSums(new_categories))
47 52
     reord = c(setdiff(1:nrow(new_categories), which(new_categories[, "Counts"] ==
48 53
                                                       0)), which(new_categories[, "Counts"] == 0))
49 54
     new_categories = new_categories[reord, ]
50 55
     new_mean_gamma = new_mean_gamma[, reord]
56
+    new_gamma = new_gamma[,reord,]
51 57
     colnames(new_mean_gamma) = apply(new_categories[, -ncol(new_categories)], 1, function(x)
52 58
       paste0(x, collapse = ""))
59
+    dimnames(new_gamma)[[2]] = apply(new_categories[, -ncol(new_categories)], 1, function(x)
60
+      paste0(x, collapse = ""))
53 61
     include_cols <- new_categories[,"Counts"] >= degree
54 62
     if (sum(include_cols) == 0) {
55
-      response <- matrix(rep(0,nrow(new_mean_gamma)),nrow=nrow(new_mean_gamma),ncol=1)
63
+      response <- matrix(rep(0,nrow(new_mean_gamma)),nrow = nrow(new_mean_gamma),ncol=1)
56 64
       rownames(response) <- rownames(new_mean_gamma)
57 65
       colnames(response) <- paste0("Pr(response|degree >=",degree,")")
58 66
     }else{
67
+      #condition on degree >= x
59 68
       response <- new_mean_gamma[,include_cols, drop = FALSE]
60
-      response <- rowMeans(response)
61
-      response <- matrix(response, ncol = 1, nrow = length(response))
62
-      rownames(response) <- rownames(new_mean_gamma)
63
-      colnames(response) <- paste0("Pr(response | degree >=",degree,")")
69
+
70
+      if (!is.null(at_least_n)) {
71
+      response <- structure(rowMeans(apply(new_gamma[,include_cols,,drop = FALSE],c(1,3),sum) >= at_least_n),
72
+                            dim = c(nrow(response),1), names = NULL, dimnames = list(rownames(response),paste0("Pr(response | degree >=",degree,")")))
73
+      }
74
+
75
+      if (!max.prob  & is.null(at_least_n)) {
76
+        response <- structure(rowMeans(response), dim = c(nrow(response),1), names = NULL, dimnames = list(rownames(response),paste0("Pr(response | degree >=",degree,")")))
77
+      }else if (max.prob  &  is.null(at_least_n)){
78
+        response <- structure(apply(response,1,max),dim=c(nrow(response),1), names = NULL, dimnames = list(rownames(response), paste0("Pr(response | degree >=",degree,")")))
79
+      }
80
+      # response <- matrix(response, ncol = 1, nrow = length(response))
81
+      # rownames(response) <- rownames(new_mean_gamma)
82
+      # colnames(response) <- paste0("Pr(response | degree >=",degree,")")
64 83
     }
65 84
     response
66 85
 }
67 86
new file mode 100644
... ...
@@ -0,0 +1,156 @@
1
+.rhat<-function(...){
2
+	#confirm all elements are the same length
3
+	cond<-diff(range(as.vector(unlist(Map(length,list(...))))))==0
4
+	if(!cond)
5
+	{
6
+		stop("Not all arugments are of equal length")
7
+	}
8
+	#rank normalization according to eq 14 of arxiv: 1903.08008.pdf
9
+	.ranknorm<-function(...){
10
+		(matrix(rank(do.call(cbind,list(...))),ncol=length(list(...)))-3/4)/(length(list(...)[[1]])-1/4)
11
+	}
12
+
13
+	phimn<-.ranknorm(...)
14
+
15
+	# mean of each chain
16
+	.phiM <- function(phimn){
17
+		colMeans(phimn)
18
+	}
19
+
20
+	#mean across chains
21
+	.phi <- function(phim){
22
+		mean(phim)
23
+	}
24
+
25
+	PHIM<-.phiM(phimn)
26
+	PHI<-.phi(PHIM)
27
+
28
+	#between chain variance
29
+	.B <- function(PHI,PHIM,PHIMN){
30
+		sum((PHIM-PHI)^2)*nrow(PHIMN)/(ncol(PHIMN)-1)
31
+	}
32
+
33
+	between<-.B(PHI,PHIM,phimn)
34
+	# s_squared
35
+	.ssq<-function(PHIMN,PHIM){
36
+		colSums((t(t(PHIMN)-PHIM))^2)/(nrow(PHIMN)-1)
37
+	}
38
+
39
+	s2<-.ssq(phimn,PHIM)
40
+	within<-mean(s2)
41
+	#Rhat
42
+	sqrt((((nrow(phimn)-1)/nrow(phimn))*within+(1/nrow(phimn))*between)/within)
43
+
44
+}
45
+
46
+
47
+#' Check the convergence of multiple COMPASS models fit with different seeds.
48
+#'
49
+#' Computes Rhat for all nsubjects x nsubsets parameters across the list of models, treated as separate chains.
50
+#' Flags cell populations and subjects with Rhat > 1.01. 
51
+#' The most frequently flagged population is passed for further diagnostis to compute Rhat between all pairs of models and
52
+#' to try and identify the model or models that are outliers.
53
+#' The outliers are removed and a list of good models is returned.
54
+#' @note Uses foreach and doMC, so it won't work on windows.
55
+#' 
56
+#' @param mlist A list of COMPASSResult models. Each should be fit to the same data, but with different seeds.
57
+#' @param ncores The number of cores to use, if supported on the system.
58
+#' @return A list of COMPASSResult models that are consistent / have converged. 
59
+#' @export
60
+#' @importFrom utils txtProgressBar setTxtProgressBar
61
+#' @import foreach
62
+#' @examples
63
+#' data(COMPASS)
64
+#' set.seed(100)
65
+#' fit <- COMPASS(CC,
66
+#'   category_filter=NULL,
67
+#'   treatment=trt == "Treatment",
68
+#'   control=trt == "Control",
69
+#'   verbose=FALSE,
70
+#'   iterations=100 ## set higher for a real analysis
71
+#' )
72
+#' set.seed(200)
73
+#' fit2 <- COMPASS(CC,
74
+#'   category_filter=NULL,
75
+#'   treatment=trt == "Treatment",
76
+#'   control=trt == "Control",
77
+#'   verbose=FALSE,
78
+#'   iterations=100 ## set higher for a real analysis
79
+#' )
80
+#' checkCOMPASSConvergence(list(fit,fit2))
81
+checkCOMPASSConvergence<-function(mlist,ncores=1){
82
+  if(!is.list(mlist)){
83
+    stop("mlist should be a list of COMPASSResult fit to the same data with different random seeds.")
84
+  }
85
+  allok<-TRUE
86
+  if(!requireNamespace("foreach",quietly=TRUE)){
87
+	  message("foreach is required to run checkCOMPASSConvergence")
88
+	  allok<-FALSE
89
+  }
90
+  if(requireNamespace("doMC",quietly=TRUE)&allok){
91
+  	doMC::registerDoMC(ncores)
92
+  }else{
93
+	message("You may want to install the doMC package")
94
+  }
95
+  if(!requireNamespace("progress",quietly=TRUE)){
96
+	  message("progress is required to run checkCOMPASSConvergence")
97
+	  allok<-FALSE
98
+  }
99
+  if(allok){
100
+  
101
+  if(length(mlist)<2){
102
+    stop("mlist must be a list of > 2 COMPASS Results fit to the same data.")
103
+  }
104
+  for(i in 2:length(mlist)){
105
+    if(!all.equal(mlist[[1]]$data,mlist[[i]]$data)){
106
+      stop("Input models are not all fit to the same data. Stopping,")
107
+    }
108
+  }
109
+  # List of models is compatible.
110
+  # Extract the gamma matrices
111
+  gammas<-Map(function(x)x$fit$gamma,mlist)
112
+  #How many subjects and cell subsets
113
+  nsamples<-dim(gammas[[1]])[1]
114
+  nsubsets<-dim(gammas[[1]])[2]
115
+  message(paste0("Checking convergence of ",nsamples*nsubsets, " parameters"))
116
+  rhat_matrix_all<-matrix(0,nrow=nsamples,ncol=nsubsets)
117
+  pb<-txtProgressBar(min=0,max=1,style=3,title = "Checking convergence...")
118
+  suppressWarnings({
119
+  rhat_matrix_all<-foreach(i = 1:nsamples,.combine = rbind,.errorhandling = "remove") %dopar% {
120
+    setTxtProgressBar(pb,max(pb$getVal(),i/nsamples))
121
+     result<-rep(0,nsubsets)
122
+    for(j in 1:nsubsets){
123
+      result[j]<-do.call(.rhat,Map(function(x)x[i,j,],gammas))
124
+    }
125
+     result
126
+   }})
127
+   
128
+   ranked_problematic_subsets<-sort(table(which(rhat_matrix_all>1.01,T)[,2]),decreasing=TRUE)
129
+   message(paste0("\nDetected convergence issues in ",length(ranked_problematic_subsets)," cell subsets"))
130
+   message("Running further diagnostics to identify outlier chains..")
131
+   top_problem_subset<-as.numeric(names(ranked_problematic_subsets)[1])
132
+   subset_phenotype<-paste0(paste(names(which(mlist[[1]]$fit$categories[top_problem_subset,]==1)),collapse="+"),"+")
133
+   subset_phenotype<-gsub("Counts\\+","",subset_phenotype)
134
+   
135
+   #pick a subject with poor convergence for this subset
136
+   j<-as.numeric(gsub("result\\.","",names(which(which(rhat_matrix_all>1.01,T)[,2]==top_problem_subset)[1])))
137
+   chains<-Map(function(x)x[j,top_problem_subset,],gammas)
138
+   combinations<-combn(length(gammas),2)
139
+   rhat_pair_matrix<-matrix(0,ncol=length(gammas),nrow=length(gammas))
140
+   for(i in 1:ncol(combinations)){
141
+     j<-combinations[,i][1]
142
+     k<-combinations[,i][2]
143
+     rhat_pair_matrix[j,k]<-.rhat(chains[[j]],chains[[k]])
144
+   }
145
+   rhat_pair_matrix[lower.tri(rhat_pair_matrix)]<-t(rhat_pair_matrix)[lower.tri(t(rhat_pair_matrix))]
146
+   drop_ind<-sapply(1:length(gammas), function(i) {
147
+     if (all(rhat_pair_matrix[, i][-i] > 1.01)) {
148
+       message(paste0("Dropping model ",i))
149
+       i
150
+     }
151
+   })
152
+   drop_ind<-unlist(Filter(function(x)!is.null(x),drop_ind))
153
+   mlist[-drop_ind]
154
+  }
155
+}
156
+
... ...
@@ -4,12 +4,22 @@
4 4
 \alias{COMPASS}
5 5
 \title{Fit the COMPASS Model}
6 6
 \usage{
7
-COMPASS(data, treatment, control, subset = NULL,
7
+COMPASS(
8
+  data,
9
+  treatment,
10
+  control,
11
+  subset = NULL,
8 12
   category_filter = function(x) colSums(x > 5) > 2,
9
-  filter_lowest_frequency = 0, filter_specific_markers = NULL,
10
-  model = "discrete", iterations = 40000, replications = 8,
11
-  keep_original_data = FALSE, verbose = TRUE, dropDegreeOne = FALSE,
12
-  ...)
13
+  filter_lowest_frequency = 0,
14
+  filter_specific_markers = NULL,
15
+  model = "discrete",
16
+  iterations = 40000,
17
+  replications = 8,
18
+  keep_original_data = FALSE,
19
+  verbose = TRUE,
20
+  dropDegreeOne = FALSE,
21
+  ...
22
+)
13 23
 }
14 24
 \arguments{
15 25
 \item{data}{An object of class \code{COMPASSContainer}.}
... ...
@@ -4,8 +4,14 @@
4 4
 \alias{COMPASSContainer}
5 5
 \title{Generate the Data Object used by COMPASS}
6 6
 \usage{
7
-COMPASSContainer(data, counts, meta, individual_id, sample_id,
8
-  countFilterThreshold = 0)
7
+COMPASSContainer(
8
+  data,
9
+  counts,
10
+  meta,
11
+  individual_id,
12
+  sample_id,
13
+  countFilterThreshold = 0
14
+)
9 15
 }
10 16
 \arguments{
11 17
 \item{data}{A list of matrices. Each matrix \code{M_i} is made up of
... ...
@@ -4,10 +4,17 @@
4 4
 \alias{COMPASSContainerFromGatingSet}
5 5
 \title{Create a COMPASS Container from a GatingSet}
6 6
 \usage{
7
-COMPASSContainerFromGatingSet(gs = NULL, node = NULL,
8
-  filter.fun = NULL, individual_id = "PTID", mp = NULL,
9
-  matchmethod = c("Levenshtein", "regex"), markers = NA,
10
-  swap = FALSE, countFilterThreshold = 5000)
7
+COMPASSContainerFromGatingSet(
8
+  gs = NULL,
9
+  node = NULL,
10
+  filter.fun = NULL,
11
+  individual_id = "PTID",
12
+  mp = NULL,
13
+  matchmethod = c("Levenshtein", "regex"),
14
+  markers = NA,
15
+  swap = FALSE,
16
+  countFilterThreshold = 5000
17
+)
11 18
 }
12 19
 \arguments{
13 20
 \item{gs}{a \code{GatingSet} or \code{GatingSetList}}
... ...
@@ -4,8 +4,13 @@
4 4
 \alias{COMPASSfitToCountsTable}
5 5
 \title{Extract a table of counts from a COMPASSResult object}
6 6
 \usage{
7
-COMPASSfitToCountsTable(x, idcol = NULL, parent = NULL, drop = NULL,
8
-  stimName = NULL)
7
+COMPASSfitToCountsTable(
8
+  x,
9
+  idcol = NULL,
10
+  parent = NULL,
11
+  drop = NULL,
12
+  stimName = NULL
13
+)
9 14
 }
10 15
 \arguments{
11 16
 \item{x}{\code{COMPASSResult}}
... ...
@@ -8,8 +8,7 @@
8 8
 \usage{
9 9
 PolyfunctionalityScore(x, degree, n, markers = NULL)
10 10
 
11
-\method{PolyfunctionalityScore}{COMPASSResult}(x, degree, n,
12
-  markers = NULL)
11
+\method{PolyfunctionalityScore}{COMPASSResult}(x, degree, n, markers = NULL)
13 12
 
14 13
 \method{PolyfunctionalityScore}{default}(x, degree, n, markers = NULL)
15 14
 }
... ...
@@ -5,9 +5,9 @@
5 5
 \alias{Response.COMPASSResult}
6 6
 \title{Compute a response probability from COMPASS mcmc samples.}
7 7
 \usage{
8
-Response(x, markers, degree)
8
+Response(x, markers, degree, max.prob, at_least_n)
9 9
 
10
-\method{Response}{COMPASSResult}(x, markers = NULL, degree = 1)
10
+\method{Response}{COMPASSResult}(x, markers = NULL, degree = 1, max.prob = FALSE, at_least_n = NULL)
11 11
 }
12 12
 \arguments{
13 13
 \item{x}{a \code{COMPASSResult} object.}
... ...
@@ -15,6 +15,10 @@ Response(x, markers, degree)
15 15
 \item{markers}{a \code{vector} of marker names.}
16 16
 
17 17
 \item{degree}{the \code{numeric} degree of functionality to test.}
18
+
19
+\item{max.prob}{\code{logical} Use the max probability rather than the average across subsets. Defaults to FALSE.}
20
+
21
+\item{at_least_n}{\code{logical} response of degree x or greater with at_least_n subsets responding.}
18 22
 }
19 23
 \value{
20 24
 A \code{vector} of response probabilities for each subject.
... ...
@@ -28,5 +32,6 @@ i.e., the probability of at least \code{degree} markers exhibiting an antigen sp
28 32
 The response is computed from the sampled Gamma matrix, subsetting on the selected markers, and
29 33
 }
30 34
 \examples{
35
+
31 36
 Response(CR, markers = c("M1","M2","M3"), degree = 2)
32 37
 }
... ...
@@ -4,8 +4,15 @@
4 4
 \alias{SimpleCOMPASS}
5 5
 \title{Fit the discrete COMPASS Model}
6 6
 \usage{
7
-SimpleCOMPASS(n_s, n_u, meta, individual_id, iterations = 10000,
8
-  replications = 8, verbose = TRUE)
7
+SimpleCOMPASS(
8
+  n_s,
9
+  n_u,
10
+  meta,
11
+  individual_id,
12
+  iterations = 10000,
13
+  replications = 8,
14
+  verbose = TRUE
15
+)
9 16
 }
10 17
 \arguments{
11 18
 \item{n_s}{The cell counts for stimulated cells.}
12 19
new file mode 100644
... ...
@@ -0,0 +1,46 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/Rhat.R
3
+\name{checkCOMPASSConvergence}
4
+\alias{checkCOMPASSConvergence}
5
+\title{Check the convergence of multiple COMPASS models fit with different seeds.}
6
+\usage{
7
+checkCOMPASSConvergence(mlist, ncores = 1)
8
+}
9
+\arguments{
10
+\item{mlist}{A list of COMPASSResult models. Each should be fit to the same data, but with different seeds.}
11
+
12
+\item{ncores}{The number of cores to use, if supported on the system.}
13
+}
14
+\value{
15
+A list of COMPASSResult models that are consistent / have converged.
16
+}
17
+\description{
18
+Computes Rhat for all nsubjects x nsubsets parameters across the list of models, treated as separate chains.
19
+Flags cell populations and subjects with Rhat > 1.01. 
20
+The most frequently flagged population is passed for further diagnostis to compute Rhat between all pairs of models and
21
+to try and identify the model or models that are outliers.
22
+The outliers are removed and a list of good models is returned.
23
+}
24
+\note{
25
+Uses foreach and doMC, so it won't work on windows.
26
+}
27
+\examples{
28
+data(COMPASS)
29
+set.seed(100)
30
+fit <- COMPASS(CC,
31
+  category_filter=NULL,
32
+  treatment=trt == "Treatment",
33
+  control=trt == "Control",
34
+  verbose=FALSE,
35
+  iterations=100 ## set higher for a real analysis
36
+)
37
+set.seed(200)
38
+fit2 <- COMPASS(CC,
39
+  category_filter=NULL,
40
+  treatment=trt == "Treatment",
41
+  control=trt == "Control",
42
+  verbose=FALSE,
43
+  iterations=100 ## set higher for a real analysis
44
+)
45
+checkCOMPASSConvergence(list(fit,fit2))
46
+}
... ...
@@ -8,8 +8,14 @@
8 8
 \usage{
9 9
 melt_(data, ...)
10 10
 
11
-\method{melt_}{data.frame}(data, id.vars, measure.vars,
12
-  variable.name = "variable", ..., value.name = "value")
11
+\method{melt_}{data.frame}(
12
+  data,
13
+  id.vars,
14
+  measure.vars,
15
+  variable.name = "variable",
16
+  ...,
17
+  value.name = "value"
18
+)
13 19
 
14 20
 \method{melt_}{matrix}(data, ...)
15 21
 }
... ...
@@ -4,24 +4,50 @@
4 4
 \alias{pheatmap}
5 5
 \title{A function to draw clustered heatmaps.}
6 6
 \usage{
7
-pheatmap(mat, color = colorRampPalette(rev(brewer.pal(n = 7, name =
8
-  "RdYlBu")))(100), kmeans_k = NA, breaks = NA,
9
-  border_color = "grey60", cellwidth = NA, cellheight = NA,
10
-  scale = "none", cluster_rows = TRUE, cluster_cols = TRUE,
7
+pheatmap(
8
+  mat,
9
+  color = colorRampPalette(rev(brewer.pal(n = 7, name = "RdYlBu")))(100),
10
+  kmeans_k = NA,
11
+  breaks = NA,
12
+  border_color = "grey60",
13
+  cellwidth = NA,
14
+  cellheight = NA,
15
+  scale = "none",
16
+  cluster_rows = TRUE,
17
+  cluster_cols = TRUE,
11 18
   clustering_distance_rows = "euclidean",
12 19
   clustering_distance_cols = "euclidean",
13
-  clustering_method = "complete", treeheight_row = ifelse(cluster_rows,
14
-  50, 0), treeheight_col = ifelse(cluster_cols, 50, 0), legend = TRUE,
15
-  legend_breaks = NA, legend_labels = NA, annotation = NA,
16
-  annotation_colors = NA, annotation_legend = TRUE,
17
-  drop_levels = TRUE, show_rownames = TRUE, show_colnames = TRUE,
18
-  main = NA, fontsize = 10, fontsize_row = fontsize,
19
-  fontsize_col = fontsize, display_numbers = FALSE,
20
-  number_format = "\%.2f", fontsize_number = 0.8 * fontsize,
21
-  filename = NA, width = NA, height = NA, row_annotation = NA,
22
-  row_annotation_legend = TRUE, row_annotation_colors = NA,
23
-  cytokine_annotation = NA, headerplot = NA, polar = FALSE,
24
-  order_by_max_functionality = TRUE, ...)
20
+  clustering_method = "complete",
21
+  treeheight_row = ifelse(cluster_rows, 50, 0),
22
+  treeheight_col = ifelse(cluster_cols, 50, 0),
23
+  legend = TRUE,
24
+  legend_breaks = NA,
25
+  legend_labels = NA,
26
+  annotation = NA,
27
+  annotation_colors = NA,
28
+  annotation_legend = TRUE,
29
+  drop_levels = TRUE,
30
+  show_rownames = TRUE,
31
+  show_colnames = TRUE,
32
+  main = NA,
33
+  fontsize = 10,
34
+  fontsize_row = fontsize,
35
+  fontsize_col = fontsize,
36
+  display_numbers = FALSE,
37
+  number_format = "\%.2f",
38
+  fontsize_number = 0.8 * fontsize,
39
+  filename = NA,
40
+  width = NA,
41
+  height = NA,
42
+  row_annotation = NA,
43
+  row_annotation_legend = TRUE,
44
+  row_annotation_colors = NA,
45
+  cytokine_annotation = NA,
46
+  headerplot = NA,
47
+  polar = FALSE,
48
+  order_by_max_functionality = TRUE,
49
+  ...
50
+)
25 51
 }
26 52
 \arguments{
27 53
 \item{mat}{numeric matrix of the values to be plotted.}
... ...
@@ -5,12 +5,24 @@
5 5
 \alias{plot}
6 6
 \title{Plot a COMPASSResult}
7 7
 \usage{
8
-\method{plot}{COMPASSResult}(x, y, subset = NULL, threshold = 0.01,
9
-  minimum_dof = 1, maximum_dof = Inf, must_express = NULL,
10
-  row_annotation, palette = colorRampPalette(brewer.pal(10,
11
-  "Purples"))(20), show_rownames = FALSE, show_colnames = FALSE,
12
-  measure = NULL, order_by = FunctionalityScore,
13
-  order_by_max_functionality = TRUE, markers = NULL, ...)
8
+\method{plot}{COMPASSResult}(
9
+  x,
10
+  y,
11
+  subset = NULL,
12
+  threshold = 0.01,
13
+  minimum_dof = 1,
14
+  maximum_dof = Inf,
15
+  must_express = NULL,
16
+  row_annotation,
17
+  palette = colorRampPalette(brewer.pal(10, "Purples"))(20),
18
+  show_rownames = FALSE,
19
+  show_colnames = FALSE,
20
+  measure = NULL,
21
+  order_by = FunctionalityScore,
22
+  order_by_max_functionality = TRUE,
23
+  markers = NULL,
24
+  ...
25
+)
14 26
 }
15 27
 \arguments{
16 28
 \item{x}{An object of class \code{COMPASSResult}.}
... ...
@@ -4,9 +4,20 @@
4 4
 \alias{plot2}
5 5
 \title{Plot a pair of COMPASSResults}
6 6
 \usage{
7
-plot2(x, y, subset, threshold = 0.01, minimum_dof = 1,
8
-  maximum_dof = Inf, must_express = NULL, row_annotation = NULL,
9
-  palette = NA, show_rownames = FALSE, show_colnames = FALSE, ...)
7
+plot2(
8
+  x,
9
+  y,
10
+  subset,
11
+  threshold = 0.01,
12
+  minimum_dof = 1,
13
+  maximum_dof = Inf,
14
+  must_express = NULL,
15
+  row_annotation = NULL,
16
+  palette = NA,
17
+  show_rownames = FALSE,
18
+  show_colnames = FALSE,
19
+  ...
20
+)
10 21
 }
11 22
 \arguments{
12 23
 \item{x}{An object of class \code{COMPASSResult}.}
... ...
@@ -4,10 +4,17 @@
4 4
 \alias{plotCOMPASSResultStack}
5 5
 \title{Plot multiple COMPASSResults}
6 6
 \usage{
7
-plotCOMPASSResultStack(x, threshold = 0.01, minimum_dof = 1,
8
-  maximum_dof = Inf, row_annotation, variable,
7
+plotCOMPASSResultStack(
8
+  x,
9
+  threshold = 0.01,
10
+  minimum_dof = 1,
11
+  maximum_dof = Inf,
12
+  row_annotation,
13
+  variable,
9 14
   palette = colorRampPalette(brewer.pal(9, "Purples"))(20),
10
-  show_rownames = FALSE, ...)
15
+  show_rownames = FALSE,
16
+  ...
17
+)
11 18
 }
12 19
 \arguments{
13 20
 \item{x}{A named list of objects of class \code{COMPASSResult}. The names are values of type \code{variable}}
... ...
@@ -4,10 +4,18 @@
4 4
 \alias{shinyCOMPASS}
5 5
 \title{Start a Shiny Application for Visualizing COMPASS Results}
6 6
 \usage{
7
-shinyCOMPASS(x, dir = NULL, meta.vars, facet1 = "None",
8
-  facet2 = "None", facet3 = "None",
7
+shinyCOMPASS(
8
+  x,
9
+  dir = NULL,
10
+  meta.vars,
11
+  facet1 = "None",
12
+  facet2 = "None",
13
+  facet3 = "None",
9 14
   main = "Heatmap of Ag-Specificity Posterior Probabilities",
10
-  stimulation = NULL, launch = TRUE, ...)
15
+  stimulation = NULL,
16
+  launch = TRUE,
17
+  ...
18
+)
11 19
 }
12 20
 \arguments{
13 21
 \item{x}{An object of class \code{COMPASSResult}.}