Browse code

get rid of most warnings

sherman5 authored on 26/01/2018 17:42:54
Showing 9 changed files

... ...
@@ -12,7 +12,7 @@ Description: Coordinated Gene Activity in Pattern Sets (CoGAPS)
12 12
     analysis.
13 13
 Maintainer: Elana J. Fertig <ejfertig@jhmi.edu>
14 14
 Depends:
15
-    R (>= 3.0.1),
15
+    R (>= 3.4.0),
16 16
     Rcpp (>= 0.11.0)
17 17
 Imports:
18 18
     RColorBrewer (>= 1.0.5),
... ...
@@ -32,6 +32,7 @@ Suggests:
32 32
     testthat,
33 33
     lintr
34 34
 LinkingTo: Rcpp, BH
35
+VignetteBuilder: knitr
35 36
 License: GPL (==2)
36 37
 biocViews: GeneExpression, Transcription, GeneSetEnrichment,
37 38
     DifferentialExpression, Bayesian, Clustering, TimeCourse, RNASeq, Microarray,
... ...
@@ -23,6 +23,7 @@
23 23
 #'  the fixed patterns
24 24
 #' @param fixedPatterns matrix of fixed values in either A or P matrix
25 25
 #' @param checkpointInterval time (in seconds) between creating a checkpoint
26
+#' @param ... keeps backwards compatibility with arguments from older versions
26 27
 #' @return list with A and P matrix estimates
27 28
 #' @importFrom methods new
28 29
 #' @export
... ...
@@ -55,11 +56,8 @@ fixedPatterns = matrix(0), checkpointInterval=0, ...)
55 56
         stop('D and S matrix must be non-negative')
56 57
 
57 58
     # run algorithm with call to C++ code
58
-    nFactor <- floor(nFactor)
59
-    nEquil <- floor(nEquil)
60
-    nSample <- floor(nSample)
61
-    result <- cogaps_cpp(D, S, nFactor, nEquil, floor(nEquil/10), nSample, nOutputs, nSnapshots,
62
-        alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages,
59
+    result <- cogaps_cpp(D, S, nFactor, nEquil, nEquil/10, nSample, nOutputs,
60
+        nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages,
63 61
         singleCellRNASeq, whichMatrixFixed, fixedPatterns, checkpointInterval)
64 62
 
65 63
     # backwards compatible with v2
... ...
@@ -94,8 +92,22 @@ displayBuildReport <- function()
94 92
 #'
95 93
 #' @param D data matrix
96 94
 #' @param S uncertainty matrix
95
+#' @param ABins unused
96
+#' @param PBins unused
97
+#' @param simulation_id unused
98
+#' @param nOutR number of output messages
99
+#' @param output_atomic unused
100
+#' @param fixedBinProbs unused
101
+#' @param fixedDomain unused
102
+#' @param sampleSnapshots indicates if snapshots should be made
103
+#' @param numSnapshots how many snapshots to take
104
+#' @param nMaxA unused
105
+#' @param nMaxP unused
106
+#' @param max_gibbmass_paraA limit truncated normal to max size
107
+#' @param max_gibbmass_paraP limit truncated normal to max size
97 108
 #' @return list with A and P matrix estimates
98 109
 #' @importFrom methods new
110
+#' @inheritParams CoGAPS
99 111
 #' @export
100 112
 gapsRun <- function(D, S, ABins=data.frame(), PBins=data.frame(), nFactor=7,
101 113
 simulation_id="simulation", nEquil=1000, nSample=1000, nOutR=1000,
... ...
@@ -115,9 +127,11 @@ alphaP=0.01, nMaxP=100000, max_gibbmass_paraP=100.0, seed=-1, messages=TRUE)
115 127
 #' @param D data matrix
116 128
 #' @param S uncertainty matrix
117 129
 #' @param FP data.frame with rows giving fixed patterns for P
130
+#' @param fixedMatrix unused
118 131
 #' @param ... v2 style parameters
119 132
 #' @return list with A and P matrix estimates
120 133
 #' @importFrom methods new
134
+#' @inheritParams gapsRun
121 135
 #' @export
122 136
 gapsMapRun <- function(D, S, FP, ABins=data.frame(), PBins=data.frame(),
123 137
 nFactor=5, simulation_id="simulation", nEquil=1000, nSample=1000, nOutR=1000,
... ...
@@ -34,7 +34,7 @@ cluster.method="complete", ignore.NA=FALSE, bySet=FALSE, ...)
34 34
     corr.dist=1-corr.dist
35 35
     # cluster
36 36
     #library(cluster)
37
-    clust=agnes(x=corr.dist,diss=T,method=cluster.method)
37
+    clust=agnes(x=corr.dist,diss=TRUE,method=cluster.method)
38 38
     cut=cutree(as.hclust(clust),k=cnt)
39 39
     #save.image(file=paste("CoGAPS.",nP,"P.",nS,"Set.CorrClustCut",cnt,".RData"))
40 40
 
... ...
@@ -1,17 +1,21 @@
1 1
 #'\code{plotSmoothPatterns} plots the output A and P matrices as a
2 2
 #' heatmap and line plot respectively
3 3
 #'
4
-#'@param P the mean A matrix
5
-#'@param x optional variables
6
-#'@param breaks breaks in plots
7
-#'@param breakStyle style of breaks
8
-#'@param orderP whether to order patterns
9
-#'@param plotPTS whether to plot points on lines
10
-#'@param pointCol color of points
11
-#'@param lineCol color of line
12
-#'@param add logical specifying if bars should be added to an already existing plot; defaults to `FALSE'.
13
-#'@param ... arguments to be passed to/from other methods.  For the default method these can include further arguments (such as `axes', `asp' and `main') and graphical parameters (see `par') which are passed to `plot.window()', `title()' and `axis'.
14
-#'@export
4
+#' @param P the mean A matrix
5
+#' @param x optional variables
6
+#' @param breaks breaks in plots
7
+#' @param breakStyle style of breaks
8
+#' @param orderP whether to order patterns
9
+#' @param plotPTS whether to plot points on lines
10
+#' @param pointCol color of points
11
+#' @param lineCol color of line
12
+#' @param add logical specifying if bars should be added to an already existing
13
+#'  plot; defaults to `FALSE'.
14
+#' @param ... arguments to be passed to/from other methods.  For the default
15
+#'  method these can include further arguments (such as `axes', `asp' and
16
+#'  `main') and graphical parameters (see `par') which are passed to
17
+#"  `plot.window()', `title()' and `axis'.
18
+#' @export
15 19
 plotSmoothPatterns <- function(P, x=NULL, breaks=NULL, breakStyle=TRUE,
16 20
 orderP=!all(is.null(x)), plotPTS=FALSE, pointCol='black', lineCol='grey',
17 21
 add=FALSE, ...)
... ...
@@ -31,7 +35,8 @@ add=FALSE, ...)
31 35
     # make the breaks in a uniform format
32 36
     if (length(breaks)==1)
33 37
     {
34
-        breaks <- as.numeric(unique(unlist(strsplit(sub("\\(","",sub("\\]","",levels(cut(x,breaks)))),split=","))))
38
+        breaks <- as.numeric(unique(unlist(strsplit(sub("\\(","",sub("\\]","",
39
+            levels(cut(x,breaks)))),split=","))))
35 40
     }
36 41
 
37 42
     # check that the style of breaks matches the number of groups
... ...
@@ -67,7 +72,7 @@ add=FALSE, ...)
67 72
         xMax <- seq(from=ncol(P)+1,length.out=nrow(P))[order(PMax,decreasing=TRUE)]
68 73
         xTmp <- x
69 74
         PTmp <- P
70
-        for (iP in order(PMax,decreasing=T))
75
+        for (iP in order(PMax,decreasing=TRUE))
71 76
         {
72 77
             if (length(xTmp) < 1)
73 78
             {
... ...
@@ -92,7 +97,7 @@ add=FALSE, ...)
92 97
     }
93 98
     else
94 99
     {
95
-        split.screen(c(nrow(P), length(which(breakStyle))), erase=F)
100
+        split.screen(c(nrow(P), length(which(breakStyle))), erase=FALSE)
96 101
     }
97 102
 
98 103
     scr <- 1
... ...
@@ -119,7 +124,7 @@ add=FALSE, ...)
119 124
 
120 125
             if (add)
121 126
             {
122
-                plot(x[idxTmp], loess(P[iP,idxTmp]~x[idxTmp])$fit, col=lineCol, type='l', axes=F, xlab='', ylab='',lwd=3,
127
+                plot(x[idxTmp], loess(P[iP,idxTmp]~x[idxTmp])$fit, col=lineCol, type='l', axes=FALSE, xlab='', ylab='',lwd=3,
123 128
                     ylim=c(0,max(P[iP,])),xlim=xBorders,...)
124 129
             }
125 130
             else
... ...
@@ -47,6 +47,8 @@ the fixed patterns}
47 47
 \item{fixedPatterns}{matrix of fixed values in either A or P matrix}
48 48
 
49 49
 \item{checkpointInterval}{time (in seconds) between creating a checkpoint}
50
+
51
+\item{...}{keeps backwards compatibility with arguments from older versions}
50 52
 }
51 53
 \value{
52 54
 list with A and P matrix estimates
... ...
@@ -19,6 +19,50 @@ gapsMapRun(D, S, FP, ABins = data.frame(), PBins = data.frame(),
19 19
 
20 20
 \item{FP}{data.frame with rows giving fixed patterns for P}
21 21
 
22
+\item{ABins}{unused}
23
+
24
+\item{PBins}{unused}
25
+
26
+\item{nFactor}{number of patterns (basis vectors, metagenes), which must be
27
+greater than or equal to the number of rows of FP}
28
+
29
+\item{simulation_id}{unused}
30
+
31
+\item{nEquil}{number of iterations for burn-in}
32
+
33
+\item{nSample}{number of iterations for sampling}
34
+
35
+\item{nOutR}{number of output messages}
36
+
37
+\item{output_atomic}{unused}
38
+
39
+\item{fixedMatrix}{unused}
40
+
41
+\item{fixedBinProbs}{unused}
42
+
43
+\item{fixedDomain}{unused}
44
+
45
+\item{sampleSnapshots}{indicates if snapshots should be made}
46
+
47
+\item{numSnapshots}{how many snapshots to take}
48
+
49
+\item{alphaA}{sparsity parameter for A domain}
50
+
51
+\item{nMaxA}{unused}
52
+
53
+\item{max_gibbmass_paraA}{limit truncated normal to max size}
54
+
55
+\item{alphaP}{sparsity parameter for P domain}
56
+
57
+\item{nMaxP}{unused}
58
+
59
+\item{max_gibbmass_paraP}{limit truncated normal to max size}
60
+
61
+\item{seed}{a positive seed is used as-is, while any negative seed tells
62
+the algorithm to pick a seed based on the current time}
63
+
64
+\item{messages}{display progress messages}
65
+
22 66
 \item{...}{v2 style parameters}
23 67
 }
24 68
 \value{
... ...
@@ -15,6 +15,48 @@ gapsRun(D, S, ABins = data.frame(), PBins = data.frame(), nFactor = 7,
15 15
 \item{D}{data matrix}
16 16
 
17 17
 \item{S}{uncertainty matrix}
18
+
19
+\item{ABins}{unused}
20
+
21
+\item{PBins}{unused}
22
+
23
+\item{nFactor}{number of patterns (basis vectors, metagenes), which must be
24
+greater than or equal to the number of rows of FP}
25
+
26
+\item{simulation_id}{unused}
27
+
28
+\item{nEquil}{number of iterations for burn-in}
29
+
30
+\item{nSample}{number of iterations for sampling}
31
+
32
+\item{nOutR}{number of output messages}
33
+
34
+\item{output_atomic}{unused}
35
+
36
+\item{fixedBinProbs}{unused}
37
+
38
+\item{fixedDomain}{unused}
39
+
40
+\item{sampleSnapshots}{indicates if snapshots should be made}
41
+
42
+\item{numSnapshots}{how many snapshots to take}
43
+
44
+\item{alphaA}{sparsity parameter for A domain}
45
+
46
+\item{nMaxA}{unused}
47
+
48
+\item{max_gibbmass_paraA}{limit truncated normal to max size}
49
+
50
+\item{alphaP}{sparsity parameter for P domain}
51
+
52
+\item{nMaxP}{unused}
53
+
54
+\item{max_gibbmass_paraP}{limit truncated normal to max size}
55
+
56
+\item{seed}{a positive seed is used as-is, while any negative seed tells
57
+the algorithm to pick a seed based on the current time}
58
+
59
+\item{messages}{display progress messages}
18 60
 }
19 61
 \value{
20 62
 list with A and P matrix estimates
... ...
@@ -26,9 +26,12 @@ plotSmoothPatterns(P, x = NULL, breaks = NULL, breakStyle = TRUE,
26 26
 
27 27
 \item{lineCol}{color of line}
28 28
 
29
-\item{add}{logical specifying if bars should be added to an already existing plot; defaults to `FALSE'.}
29
+\item{add}{logical specifying if bars should be added to an already existing
30
+plot; defaults to `FALSE'.}
30 31
 
31
-\item{...}{arguments to be passed to/from other methods.  For the default method these can include further arguments (such as `axes', `asp' and `main') and graphical parameters (see `par') which are passed to `plot.window()', `title()' and `axis'.}
32
+\item{...}{arguments to be passed to/from other methods.  For the default
33
+method these can include further arguments (such as `axes', `asp' and
34
+`main') and graphical parameters (see `par') which are passed to}
32 35
 }
33 36
 \description{
34 37
 \code{plotSmoothPatterns} plots the output A and P matrices as a
... ...
@@ -1,13 +1,15 @@
1 1
 ---
2 2
 title: "GWCoGAPS and PatternMarkers Vignette"
3 3
 author: "Genevieve L. Stein-O'Brien"
4
-date: \today
5
-output: BiocStyle::pdf_document
4
+date: "`r doc_date()`"
5
+package: "`r pkg_ver('CoGAPS')`"
6 6
 bibliography: AppNote.bib
7 7
 vignette: >
8
-  %\VignetteIndexEntry{Overview of CNPBayes package}
8
+  %\VignetteIndexEntry{GWCoGAPS and PatternMarkers}
9 9
   %\VignetteEngine{knitr::rmarkdown}
10
-  %\usepackage[utf8]{inputenc} 
10
+  %\VignetteEncoding{UTF-8}
11
+output: 
12
+  BiocStyle::html_document
11 13
 ---
12 14
 
13 15
 # Introduction
... ...
@@ -25,11 +27,13 @@ pipeline for genome wide NMF analysis.
25 27
 The GWCoGAPS algorithm is run by calling the GWCoGAPS function in the CoGAPS
26 28
 R package as follows:
27 29
 
28
-```{r, eval=FALSE}
29
-library(CoGAPS) 
30
+```{r}
31
+library(CoGAPS)
32
+```
33
+***
30 34
 GWCoGAPS(D, S, nFactor, nSets, nCores, saveBySetResults, fname,
31 35
     PatternsMatchFN = patternMatch4Parallel, Cut, minNS, ...)
32
-```
36
+***
33 37
 
34 38
 **Input Arguments**
35 39
 The inputs that must be set each time are only the nSets, nFactor, and data and standard deviation matrices, with all other inputs having default values. Additional inputs to the gapsRun function, as outlined previously, can be used to taylor the analysis based on the expected dimensionality of the data. GWCoGAPS specific arguments are as follows:
... ...
@@ -54,14 +58,15 @@ greater than or equal to the number of rows of FP}
54 58
 
55 59
 \par In this example, we use the same simulated data in SimpSim (SimpSim.D), as previously described, with three known patterns (SimpSim.P) and corresponding amplitude (SimpSim.A) with specified activity in two gene sets (GSets).
56 60
 
57
-```{r , eval=FALSE}
61
+***
58 62
 library('CoGAPS')
59 63
 data('SimpSim')
60 64
 GWCoGAPS(SimpSim.D, SimpSim.S, nFactor=3, nCores=NA, nSets=2,
61 65
             fname="test" ,PatternsMatchFN = postCoGAPSPatternMatch,
62 66
             sampleSnapshots = "TRUE", numSnapshots = 3)
63 67
 plotGAPS(AP.Fixed$A, AP.Fixed$P, 'ModSimFigs')
64
-```
68
+***
69
+
65 70
 Figure \ref{fig:ModSim} shows the results from plotting the GWCoGAPS estimates of ${\bf{A}}$ and ${\bf{P}}$ using \texttt{plotGAPS}.  
66 71
 \begin{figure}[ht]
67 72
   \begin{center}
... ...
@@ -113,11 +118,14 @@ Parallelizing the GAPS using the doParallel package returns a list containing th
113 118
 \item[PSnapshots]{Samples of P matrices taken during sampling.}
114 119
 \end{description}
115 120
 To ease accross set pattern comparisons, the reOrderBySet function restructures this list such that all nSets sets solution for Amean, Pmean, and Asd are listed under ${\bf{A}} ,{\bf{P}}$, and ${\bf{Asd}}$, respectively. NMF solutions using the same syntax can also be imput to reOrderBySet via the AP arguement as follows:
116
-```{r, eval=FALSE}
121
+
122
+***
117 123
 BySet<-reOrderBySet(AP=AP,nFactor=nFactor,nSets=nSets)
118
-```
124
+***
125
+
119 126
 The resulting list of pattern matrixes, i.e. BySet$P, can serve as input for the patternMatch4Parallel function or further transformed for alternative accross set pattern matching techniques. Manual curration of pattern matching can be accomplished by iterating between the patternMatch4Parallel function and visual editting using the PatternMatcher as follows: 
120
-```{r , eval=FALSE}
127
+
128
+***
121 129
 matchedPs<-patternMatch4Parallel(Ptot=BySet$P,nP=nFactor,nS=nSets,
122 130
                                  cnt=nFactor,minNS=minNS,bySet=TRUE)
123 131
 selectPBySet<-PatternMatcher(PBySet=matchedPs[["PBySet"]])
... ...
@@ -127,13 +135,14 @@ rownames(selectPBySet)<-selectPBySet$BySet
127 135
 selectPBySet<-as.matrix(selectPBySet[,-1])
128 136
 matchedPs<-patternMatch4Parallel(Ptot=selectPBySet,nP=nFactor,nS=nSets,
129 137
                                  cnt=nFactor,minNS=minNS,bySet=FALSE)
130
-```
138
+***
139
+
131 140
 The output of this process, matchedPs, is a data.frame of consensus patterns which can be directly read into the FP arguement of gapsMapRun. These patterns are scaled to have a maximum of one to allow for direct accross pattern comparisions of the ${\bf{A}}$ values both within and accross parallel sets. 
132 141
 
133 142
 ### Example: Simulated data
134 143
 \par This example will manually generate the same result as calling the GWCoGAPS function as given in the example in the previous section.
135 144
 
136
-```{r , eval=FALSE}
145
+***
137 146
 data('SimpSim')
138 147
 D<-SimpSim.D
139 148
 S<-SimpSim.S
... ...
@@ -190,8 +199,7 @@ Fixed <- foreach(i=1:nSets) %dopar% {
190 199
 
191 200
 #extract A and Asds
192 201
 As4fixPs <- postFixed(AP.fixed=Fixed,setPs=matchedPs)
193
-```
194
-
202
+***
195 203
 
196 204
 # PatternMarkers
197 205
 
... ...
@@ -212,10 +220,10 @@ where  are the elements of the $\bf{A}$ matrix for the $\textit{i}^{th}$ gene sc
212 220
 
213 221
 The PatternMarkers statistic is run by calling thepatternMarkers function in the CoGAPS R package as follows:
214 222
 
215
-```{r , eval=FALSE}
223
+***
216 224
  patternMarkers(Amatrix = AP$Amean, scaledPmatrix = FALSE, Pmatrix = NA,
217 225
   threshold = "All", lp = NA, full = FALSE, ...)
218
-```
226
+***
219 227
 
220 228
 **Input Arguments**
221 229
 \begin{description}
... ...
@@ -229,11 +237,11 @@ The PatternMarkers statistic is run by calling thepatternMarkers function in the
229 237
 
230 238
 Once the PatternMarkers statistic has been run, a heatmap of each markers expression level can be displayed using the plotPatternMarkers function as follows:
231 239
 
232
-```{r , eval=FALSE}
240
+***
233 241
 plotPatternMarkers(data = NA, patternMarkers = PatternMarkers,
234 242
       patternPalette = NA, sampleNames = NA, samplePalette = NA,
235 243
       colDenogram = TRUE, heatmapCol = "bluered", scale = "row", ...)
236
-```
244
+***
237 245
  
238 246
 **Input Arguments**
239 247
 \begin{description}
... ...
@@ -246,10 +254,10 @@ plotPatternMarkers(data = NA, patternMarkers = PatternMarkers,
246 254
 
247 255
 ### Example: Simulated data
248 256
 
249
-```{r , eval=FALSE}
257
+***
250 258
 PatternMarkers<-patternMarkers(Amatrix=AP.fixed$A,scaledPmatrix=TRUE,threshold="cut")
251 259
 plotPatternMarkers(data=D,patternMarkers=PatternMarkers,patternPalette=c("grey","navy","orange"))
252
-```
260
+***
253 261
 
254 262
 Figure \ref{fig:PM1} shows the results from running plotPatternMarkers on the PatternMarkers generated from the the GWCoGAPS results generated from the simulated data as previously illustrated.
255 263
 \begin{figure}[h]