... | ... |
@@ -1,7 +1,8 @@ |
1 | 1 |
Package: Glimma |
2 | 2 |
Type: Package |
3 | 3 |
Title: Interactive HTML graphics |
4 |
-Version: 1.15.1 |
|
4 |
+Version: 1.13.2 |
|
5 |
+Date: 2016-12-21 |
|
5 | 6 |
Authors@R: |
6 | 7 |
c( |
7 | 8 |
person( |
... | ... |
@@ -54,7 +55,7 @@ Suggests: |
54 | 55 |
License: GPL-3 | file LICENSE |
55 | 56 |
URL: https://github.com/Shians/Glimma |
56 | 57 |
BugReports: https://github.com/Shians/Glimma/issues |
57 |
-RoxygenNote: 6.1.1 |
|
58 |
+RoxygenNote: 7.1.0 |
|
58 | 59 |
NeedsCompilation: no |
59 | 60 |
LazyData: true |
60 | 61 |
VignetteBuilder: knitr |
... | ... |
@@ -31,7 +31,7 @@ checkObjAnnoCountsShapes <- function(anno, counts, x) { |
31 | 31 |
|
32 | 32 |
# check that side.main exists as a column in either anno or main object |
33 | 33 |
checkSideMainPresent <- function(side.main, anno, x) { |
34 |
- if (class(x) == "DGELRT" || class(x) == "DGEExact") { |
|
34 |
+ if (is(x, "DGELRT") || is(x, "DGEExact")) { |
|
35 | 35 |
if (side.main %!in% union(colnames(anno), colnames(x$table))) { |
36 | 36 |
stop(paste("column", quotify(side.main), "cannot be found in x$table or anno.")) |
37 | 37 |
} |
... | ... |
@@ -40,7 +40,7 @@ checkSideMainPresent <- function(side.main, anno, x) { |
40 | 40 |
} else { |
41 | 41 |
combined_anno <- anno |
42 | 42 |
} |
43 |
- } else if (class(x) == "MArrayLM") { |
|
43 |
+ } else if (is(x, "MArrayLM")) { |
|
44 | 44 |
if (side.main %!in% union(colnames(anno), colnames(x$genes))) { |
45 | 45 |
stop(paste("column", quotify(side.main), "cannot be found in x$genes or anno.")) |
46 | 46 |
} |
... | ... |
@@ -49,7 +49,7 @@ checkSideMainPresent <- function(side.main, anno, x) { |
49 | 49 |
} else { |
50 | 50 |
combined_anno <- anno |
51 | 51 |
} |
52 |
- } else if (class(x) == "DESeqResults") { |
|
52 |
+ } else if (is(x, "DESeqResults")) { |
|
53 | 53 |
if (side.main %!in% union(colnames(anno), names(x@listData))) { |
54 | 54 |
stop(paste("column", quotify(side.main), "cannot be found in x or anno.")) |
55 | 55 |
} |
... | ... |
@@ -68,4 +68,4 @@ checkSideMainPresent <- function(side.main, anno, x) { |
68 | 68 |
combined_anno <- anno |
69 | 69 |
} |
70 | 70 |
} |
71 |
-} |
|
72 | 71 |
\ No newline at end of file |
72 |
+} |
... | ... |
@@ -29,7 +29,7 @@ |
29 | 29 |
#' des <- model.matrix(~genotype) |
30 | 30 |
#' |
31 | 31 |
#' ## Apply voom with sample quality weights and fit linear model |
32 |
-#' v <- voomWithQualityWeights(x, design=des, normalize.method="none", plot=FALSE) |
|
32 |
+#' v <- voomWithQualityWeights(x, design=des, plot=FALSE) |
|
33 | 33 |
#' vfit <- lmFit(v,des) |
34 | 34 |
#' |
35 | 35 |
#' ## Apply treat relative to a fold-change of 1.5 |
... | ... |
@@ -57,7 +57,6 @@ glMDPlot <- function(x, ...) { |
57 | 57 |
#' |
58 | 58 |
#' @author Shian Su |
59 | 59 |
#' |
60 |
-#' @inheritParams glMDPlot |
|
61 | 60 |
#' @param x the data.frame object containing expression and fold change values. |
62 | 61 |
#' @param xval the column to plot on x axis of left plot. |
63 | 62 |
#' @param yval the column to plot on y axis of left plot. |
... | ... |
@@ -185,7 +184,6 @@ glMDPlot.default <- function( |
185 | 184 |
#' |
186 | 185 |
#' @author Shian Su |
187 | 186 |
#' |
188 |
-#' @inheritParams glMDPlot |
|
189 | 187 |
#' @param x the DGELRT object. |
190 | 188 |
#' @param counts the matrix of expression values, with samples in columns. |
191 | 189 |
#' @param anno the data.frame containing gene annotations. |
... | ... |
@@ -368,7 +366,7 @@ glMDPlot.DGEExact <- glMDPlot.DGELRT |
368 | 366 |
#' des <- model.matrix(~genotype) |
369 | 367 |
#' |
370 | 368 |
#' ## Apply voom with sample quality weights and fit linear model |
371 |
-#' v <- voomWithQualityWeights(x, design=des, normalize.method="none", plot=FALSE) |
|
369 |
+#' v <- voomWithQualityWeights(x, design=des, plot=FALSE) |
|
372 | 370 |
#' vfit <- lmFit(v,des) |
373 | 371 |
#' |
374 | 372 |
#' ## Apply treat relative to a fold-change of 1.5 |
... | ... |
@@ -118,7 +118,7 @@ glMDSPlot.default <- function( |
118 | 118 |
# Method for MDS objects |
119 | 119 |
points <- a1$points |
120 | 120 |
|
121 |
- if (!is.data.frame(groups) && class(groups) != "DataFrame") { |
|
121 |
+ if (!is.data.frame(groups) && !is(groups, "DataFrame")) { |
|
122 | 122 |
# Rename for the column name in dataframe |
123 | 123 |
groups <- data.frame(groups) |
124 | 124 |
} |
... | ... |
@@ -203,7 +203,7 @@ glMDSPlot.DGEList <- function ( |
203 | 203 |
labels = NULL, |
204 | 204 |
groups = rep(1, ncol(x)), |
205 | 205 |
gene.selection = c("pairwise", "common"), |
206 |
- prior.count = 0.25, |
|
206 |
+ prior.count = 2, |
|
207 | 207 |
main = "MDS Plot", |
208 | 208 |
path = getwd(), |
209 | 209 |
folder = "glimma-plots", |
... | ... |
@@ -292,16 +292,16 @@ glMDSPlot.DESeqDataSet <- function( |
292 | 292 |
|
293 | 293 |
# extract sample groups based on object class |
294 | 294 |
getLabels <- function(x, labels) { |
295 |
- |
|
295 |
+ |
|
296 | 296 |
if (is.null(labels)) { |
297 |
- if (class(x) == "DGEList") { |
|
298 |
- # DGElist get from |
|
297 |
+ if (is(x, "DGEList")) { |
|
298 |
+ # DGElist get from |
|
299 | 299 |
if (not.null(x$samples$groups)) { |
300 | 300 |
labels <- rownames(x$samples) |
301 | 301 |
} else { |
302 | 302 |
labels <- seq_cols(x) |
303 | 303 |
} |
304 |
- } else if (class(x) == "DESeqDataSet") { |
|
304 |
+ } else if (is(x, "DESeqDataSet")) { |
|
305 | 305 |
# DESeqDaset |
306 | 306 |
if (not.null(SummarizedExperiment::colData(x))) { |
307 | 307 |
labels <- rownames(SummarizedExperiment::colData(x)) |
... | ... |
@@ -28,7 +28,7 @@ glimma <- function(..., layout=c(1, 1), path=getwd(), folder="glimma-plots", |
28 | 28 |
## |
29 | 29 |
# Input checking |
30 | 30 |
for (i in list(...)) { |
31 |
- if (class(i) == "jschart") { |
|
31 |
+ if (is(i, "jschart")) { |
|
32 | 32 |
nplots <- nplots + 1 |
33 | 33 |
} |
34 | 34 |
} |
... | ... |
@@ -82,7 +82,7 @@ glimma <- function(..., layout=c(1, 1), path=getwd(), folder="glimma-plots", |
82 | 82 |
) |
83 | 83 |
|
84 | 84 |
cat( |
85 |
- temp, |
|
85 |
+ temp, |
|
86 | 86 |
file = file.path(path, folder, paste0(html, ".html")), |
87 | 87 |
sep = "\n" |
88 | 88 |
) |
... | ... |
@@ -1,13 +1,15 @@ |
1 |
-Changes IN Glimma 1.15.1 |
|
2 |
- * Updated unit test for new default colour palette in R 4.0.0 |
|
1 |
+Changes in Glimma 1.9.4 |
|
3 | 2 |
|
4 |
-Changes IN Glimma 1.6.0 |
|
3 |
+ * Fixed tests for R4.0.0 |
|
4 |
+ * Fixed examples for limma voom (normlization argument is now normalize.method) |
|
5 |
+ |
|
6 |
+Changes in Glimma 1.6.0 |
|
5 | 7 |
|
6 | 8 |
* Added table to MDS plot. |
7 | 9 |
* Changed encoding of javascript data to be more compact |
8 | 10 |
* Fixed handling of top and gene.selection parameters in glMDSPlot |
9 | 11 |
|
10 |
-CHANGES IN Glimma 1.3.0 |
|
12 |
+Changes in Glimma 1.3.0 |
|
11 | 13 |
|
12 | 14 |
* Added highlighting to bars in MDS plot. |
13 | 15 |
* Added interaction with table when clicking on points in MD plot. |
... | ... |
@@ -16,7 +18,7 @@ CHANGES IN Glimma 1.3.0 |
16 | 18 |
* Changed style of table. |
17 | 19 |
* Changed size of highlighted points. |
18 | 20 |
|
19 |
-CHANGES IN Glimma 1.2.0 |
|
21 |
+Changes in Glimma 1.2.0 |
|
20 | 22 |
|
21 | 23 |
* Added option to turn off internal cpm transform (transform=FALSE) in MD Plot. |
22 | 24 |
* Added gridlines to MD Plot. |
... | ... |
@@ -31,27 +33,27 @@ CHANGES IN Glimma 1.2.0 |
31 | 33 |
* Fixed logical values in annotation breaking graphs. |
32 | 34 |
* Fixed numeric values not working for colours. |
33 | 35 |
|
34 |
-CHANGES IN Glimma 1.1.0 |
|
36 |
+Changes in Glimma 1.1.0 |
|
35 | 37 |
|
36 | 38 |
* Added tables to MD Plot. |
37 | 39 |
|
38 |
-CHANGES IN Glimma 1.0.0 |
|
40 |
+Changes in Glimma 1.0.0 |
|
39 | 41 |
|
40 | 42 |
* Bioconductor release version. |
41 | 43 |
|
42 |
-CHANGES IN Glimma 0.99.4: |
|
44 |
+Changes in Glimma 0.99.4: |
|
43 | 45 |
|
44 | 46 |
* Added sample colours for MD plot. |
45 | 47 |
* Added DESeqResults method for glMDPlot |
46 | 48 |
|
47 |
-CHANGES IN Glimma 0.99.3: |
|
49 |
+Changes in Glimma 0.99.3: |
|
48 | 50 |
|
49 | 51 |
* Imported p.adjust for relevant functions. |
50 | 52 |
|
51 |
-CHANGES IN Glimma 0.99.2: |
|
53 |
+Changes in Glimma 0.99.2: |
|
52 | 54 |
|
53 | 55 |
* Added don't test cases for non-exported functions to pass checks. |
54 | 56 |
|
55 |
-CHANGES IN Glimma 0.99.1: |
|
57 |
+Changes in Glimma 0.99.1: |
|
56 | 58 |
|
57 | 59 |
* Initial package creation. |
... | ... |
@@ -4,10 +4,23 @@ |
4 | 4 |
\alias{glBar.default} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glBar}{default}(x, yval, names.arg = rownames(x), |
|
8 |
- ndigits = NULL, signif = 6, xlab = NULL, ylab = yval, |
|
9 |
- main = NULL, height = 400, width = 500, colval = NULL, |
|
10 |
- annot = yval, flag = NULL, info = NULL, ...) |
|
7 |
+\method{glBar}{default}( |
|
8 |
+ x, |
|
9 |
+ yval, |
|
10 |
+ names.arg = rownames(x), |
|
11 |
+ ndigits = NULL, |
|
12 |
+ signif = 6, |
|
13 |
+ xlab = NULL, |
|
14 |
+ ylab = yval, |
|
15 |
+ main = NULL, |
|
16 |
+ height = 400, |
|
17 |
+ width = 500, |
|
18 |
+ colval = NULL, |
|
19 |
+ annot = yval, |
|
20 |
+ flag = NULL, |
|
21 |
+ info = NULL, |
|
22 |
+ ... |
|
23 |
+) |
|
11 | 24 |
} |
12 | 25 |
\arguments{ |
13 | 26 |
\item{x}{the data.frame containing data to plot.} |
... | ... |
@@ -4,15 +4,32 @@ |
4 | 4 |
\alias{glMDPlot.DESeqDataSet} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{DESeqDataSet}(x, counts = NULL, anno, groups, |
|
8 |
- samples = NULL, status = rep(0, nrow(x)), transform = FALSE, |
|
9 |
- main = "", xlab = "Mean Expression", ylab = "log-fold-change", |
|
10 |
- side.xlab = "Group", side.ylab = "logMean", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{DESeqDataSet}( |
|
8 |
+ x, |
|
9 |
+ counts = NULL, |
|
10 |
+ anno, |
|
11 |
+ groups, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(x)), |
|
14 |
+ transform = FALSE, |
|
15 |
+ main = "", |
|
16 |
+ xlab = "Mean Expression", |
|
17 |
+ ylab = "log-fold-change", |
|
18 |
+ side.xlab = "Group", |
|
19 |
+ side.ylab = "logMean", |
|
20 |
+ side.log = FALSE, |
|
11 | 21 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
12 |
- jitter = 30, side.main = "GeneID", display.columns = NULL, |
|
22 |
+ jitter = 30, |
|
23 |
+ side.main = "GeneID", |
|
24 |
+ display.columns = NULL, |
|
13 | 25 |
cols = c("#00bfff", "#858585", "#ff3030"), |
14 |
- sample.cols = rep("#1f77b4", ncol(x)), path = getwd(), |
|
15 |
- folder = "glimma-plots", html = "MD-Plot", launch = TRUE, ...) |
|
26 |
+ sample.cols = rep("#1f77b4", ncol(x)), |
|
27 |
+ path = getwd(), |
|
28 |
+ folder = "glimma-plots", |
|
29 |
+ html = "MD-Plot", |
|
30 |
+ launch = TRUE, |
|
31 |
+ ... |
|
32 |
+) |
|
16 | 33 |
} |
17 | 34 |
\arguments{ |
18 | 35 |
\item{x}{the DESeqDataSet object.} |
... | ... |
@@ -4,15 +4,32 @@ |
4 | 4 |
\alias{glMDPlot.DESeqResults} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{DESeqResults}(x, counts = NULL, anno, groups, |
|
8 |
- samples = NULL, status = rep(0, nrow(x)), transform = FALSE, |
|
9 |
- main = "", xlab = "Mean Expression", ylab = "log-fold-change", |
|
10 |
- side.xlab = "Group", side.ylab = "Expression", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{DESeqResults}( |
|
8 |
+ x, |
|
9 |
+ counts = NULL, |
|
10 |
+ anno, |
|
11 |
+ groups, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(x)), |
|
14 |
+ transform = FALSE, |
|
15 |
+ main = "", |
|
16 |
+ xlab = "Mean Expression", |
|
17 |
+ ylab = "log-fold-change", |
|
18 |
+ side.xlab = "Group", |
|
19 |
+ side.ylab = "Expression", |
|
20 |
+ side.log = FALSE, |
|
11 | 21 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
12 |
- jitter = 30, side.main = "GeneID", display.columns = NULL, |
|
22 |
+ jitter = 30, |
|
23 |
+ side.main = "GeneID", |
|
24 |
+ display.columns = NULL, |
|
13 | 25 |
cols = c("#00bfff", "#858585", "#ff3030"), |
14 |
- sample.cols = rep("#1f77b4", ncol(counts)), path = getwd(), |
|
15 |
- folder = "glimma-plots", html = "MD-Plot", launch = TRUE, ...) |
|
26 |
+ sample.cols = rep("#1f77b4", ncol(counts)), |
|
27 |
+ path = getwd(), |
|
28 |
+ folder = "glimma-plots", |
|
29 |
+ html = "MD-Plot", |
|
30 |
+ launch = TRUE, |
|
31 |
+ ... |
|
32 |
+) |
|
16 | 33 |
} |
17 | 34 |
\arguments{ |
18 | 35 |
\item{x}{the DESeqResults object.} |
... | ... |
@@ -4,16 +4,33 @@ |
4 | 4 |
\alias{glMDPlot.DGEExact} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{DGEExact}(x, counts = NULL, anno = NULL, |
|
8 |
- groups = NULL, samples = NULL, status = rep(0, nrow(x)), |
|
9 |
- transform = FALSE, main = "", xlab = "Average log CPM", |
|
10 |
- ylab = "log-fold-change", side.xlab = "Group", |
|
11 |
- side.ylab = "Expression", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{DGEExact}( |
|
8 |
+ x, |
|
9 |
+ counts = NULL, |
|
10 |
+ anno = NULL, |
|
11 |
+ groups = NULL, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(x)), |
|
14 |
+ transform = FALSE, |
|
15 |
+ main = "", |
|
16 |
+ xlab = "Average log CPM", |
|
17 |
+ ylab = "log-fold-change", |
|
18 |
+ side.xlab = "Group", |
|
19 |
+ side.ylab = "Expression", |
|
20 |
+ side.log = FALSE, |
|
12 | 21 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
13 |
- p.adj.method = "BH", jitter = 30, side.main = "GeneID", |
|
14 |
- display.columns = NULL, cols = c("#00bfff", "#858585", "#ff3030"), |
|
15 |
- sample.cols = rep("#1f77b4", ncol(counts)), path = getwd(), |
|
16 |
- folder = "glimma-plots", html = "MD-Plot", launch = TRUE, ...) |
|
22 |
+ p.adj.method = "BH", |
|
23 |
+ jitter = 30, |
|
24 |
+ side.main = "GeneID", |
|
25 |
+ display.columns = NULL, |
|
26 |
+ cols = c("#00bfff", "#858585", "#ff3030"), |
|
27 |
+ sample.cols = rep("#1f77b4", ncol(counts)), |
|
28 |
+ path = getwd(), |
|
29 |
+ folder = "glimma-plots", |
|
30 |
+ html = "MD-Plot", |
|
31 |
+ launch = TRUE, |
|
32 |
+ ... |
|
33 |
+) |
|
17 | 34 |
} |
18 | 35 |
\arguments{ |
19 | 36 |
\item{x}{the DGEExact object.} |
... | ... |
@@ -4,16 +4,33 @@ |
4 | 4 |
\alias{glMDPlot.DGELRT} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{DGELRT}(x, counts = NULL, anno = NULL, |
|
8 |
- groups = NULL, samples = NULL, status = rep(0, nrow(x)), |
|
9 |
- transform = FALSE, main = "", xlab = "Average log CPM", |
|
10 |
- ylab = "log-fold-change", side.xlab = "Group", |
|
11 |
- side.ylab = "Expression", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{DGELRT}( |
|
8 |
+ x, |
|
9 |
+ counts = NULL, |
|
10 |
+ anno = NULL, |
|
11 |
+ groups = NULL, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(x)), |
|
14 |
+ transform = FALSE, |
|
15 |
+ main = "", |
|
16 |
+ xlab = "Average log CPM", |
|
17 |
+ ylab = "log-fold-change", |
|
18 |
+ side.xlab = "Group", |
|
19 |
+ side.ylab = "Expression", |
|
20 |
+ side.log = FALSE, |
|
12 | 21 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
13 |
- p.adj.method = "BH", jitter = 30, side.main = "GeneID", |
|
14 |
- display.columns = NULL, cols = c("#00bfff", "#858585", "#ff3030"), |
|
15 |
- sample.cols = rep("#1f77b4", ncol(counts)), path = getwd(), |
|
16 |
- folder = "glimma-plots", html = "MD-Plot", launch = TRUE, ...) |
|
22 |
+ p.adj.method = "BH", |
|
23 |
+ jitter = 30, |
|
24 |
+ side.main = "GeneID", |
|
25 |
+ display.columns = NULL, |
|
26 |
+ cols = c("#00bfff", "#858585", "#ff3030"), |
|
27 |
+ sample.cols = rep("#1f77b4", ncol(counts)), |
|
28 |
+ path = getwd(), |
|
29 |
+ folder = "glimma-plots", |
|
30 |
+ html = "MD-Plot", |
|
31 |
+ launch = TRUE, |
|
32 |
+ ... |
|
33 |
+) |
|
17 | 34 |
} |
18 | 35 |
\arguments{ |
19 | 36 |
\item{x}{the DGELRT object.} |
... | ... |
@@ -4,16 +4,34 @@ |
4 | 4 |
\alias{glMDPlot.MArrayLM} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{MArrayLM}(x, counts = NULL, anno = NULL, |
|
8 |
- groups = NULL, samples = NULL, status = rep(0, nrow(x)), |
|
9 |
- transform = FALSE, main = "", xlab = "Average log CPM", |
|
10 |
- ylab = "log-fold-change", side.main = "GeneID", |
|
11 |
- side.xlab = "Group", side.ylab = "Expression", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{MArrayLM}( |
|
8 |
+ x, |
|
9 |
+ counts = NULL, |
|
10 |
+ anno = NULL, |
|
11 |
+ groups = NULL, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(x)), |
|
14 |
+ transform = FALSE, |
|
15 |
+ main = "", |
|
16 |
+ xlab = "Average log CPM", |
|
17 |
+ ylab = "log-fold-change", |
|
18 |
+ side.main = "GeneID", |
|
19 |
+ side.xlab = "Group", |
|
20 |
+ side.ylab = "Expression", |
|
21 |
+ side.log = FALSE, |
|
12 | 22 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
13 |
- coef = ncol(x$coefficients), p.adj.method = "BH", jitter = 30, |
|
14 |
- display.columns = NULL, cols = c("#00bfff", "#858585", "#ff3030"), |
|
15 |
- sample.cols = rep("#1f77b4", ncol(counts)), path = getwd(), |
|
16 |
- folder = "glimma-plots", html = "MD-Plot", launch = TRUE, ...) |
|
23 |
+ coef = ncol(x$coefficients), |
|
24 |
+ p.adj.method = "BH", |
|
25 |
+ jitter = 30, |
|
26 |
+ display.columns = NULL, |
|
27 |
+ cols = c("#00bfff", "#858585", "#ff3030"), |
|
28 |
+ sample.cols = rep("#1f77b4", ncol(counts)), |
|
29 |
+ path = getwd(), |
|
30 |
+ folder = "glimma-plots", |
|
31 |
+ html = "MD-Plot", |
|
32 |
+ launch = TRUE, |
|
33 |
+ ... |
|
34 |
+) |
|
17 | 35 |
} |
18 | 36 |
\arguments{ |
19 | 37 |
\item{x}{the MArrayLM object.} |
... | ... |
@@ -103,7 +121,7 @@ x <- calcNormFactors(x, method="TMM") |
103 | 121 |
des <- model.matrix(~genotype) |
104 | 122 |
|
105 | 123 |
## Apply voom with sample quality weights and fit linear model |
106 |
-v <- voomWithQualityWeights(x, design=des, normalize.method="none", plot=FALSE) |
|
124 |
+v <- voomWithQualityWeights(x, design=des, plot=FALSE) |
|
107 | 125 |
vfit <- lmFit(v,des) |
108 | 126 |
|
109 | 127 |
## Apply treat relative to a fold-change of 1.5 |
... | ... |
@@ -38,7 +38,7 @@ x <- calcNormFactors(x, method="TMM") |
38 | 38 |
des <- model.matrix(~genotype) |
39 | 39 |
|
40 | 40 |
## Apply voom with sample quality weights and fit linear model |
41 |
-v <- voomWithQualityWeights(x, design=des, normalize.method="none", plot=FALSE) |
|
41 |
+v <- voomWithQualityWeights(x, design=des, plot=FALSE) |
|
42 | 42 |
vfit <- lmFit(v,des) |
43 | 43 |
|
44 | 44 |
## Apply treat relative to a fold-change of 1.5 |
... | ... |
@@ -4,16 +4,34 @@ |
4 | 4 |
\alias{glMDPlot.default} |
5 | 5 |
\title{Glimma MD Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDPlot}{default}(x, xval, yval, counts = NULL, anno = NULL, |
|
8 |
- groups = NULL, samples = NULL, status = rep(0, nrow(x)), |
|
9 |
- transform = FALSE, main = "", xlab = xval, ylab = yval, |
|
10 |
- side.main = "GeneID", side.xlab = "Group", |
|
11 |
- side.ylab = "Expression", side.log = FALSE, |
|
7 |
+\method{glMDPlot}{default}( |
|
8 |
+ x, |
|
9 |
+ xval, |
|
10 |
+ yval, |
|
11 |
+ counts = NULL, |
|
12 |
+ anno = NULL, |
|
13 |
+ groups = NULL, |
|
14 |
+ samples = NULL, |
|
15 |
+ status = rep(0, nrow(x)), |
|
16 |
+ transform = FALSE, |
|
17 |
+ main = "", |
|
18 |
+ xlab = xval, |
|
19 |
+ ylab = yval, |
|
20 |
+ side.main = "GeneID", |
|
21 |
+ side.xlab = "Group", |
|
22 |
+ side.ylab = "Expression", |
|
23 |
+ side.log = FALSE, |
|
12 | 24 |
side.gridstep = ifelse(!transform || side.log, FALSE, 0.5), |
13 |
- jitter = 30, display.columns = side.main, cols = c("#00bfff", |
|
14 |
- "#858585", "#ff3030"), sample.cols = rep("#1f77b4", ncol(counts)), |
|
15 |
- path = getwd(), folder = "glimma-plots", html = "MD-Plot", |
|
16 |
- launch = TRUE, ...) |
|
25 |
+ jitter = 30, |
|
26 |
+ display.columns = side.main, |
|
27 |
+ cols = c("#00bfff", "#858585", "#ff3030"), |
|
28 |
+ sample.cols = rep("#1f77b4", ncol(counts)), |
|
29 |
+ path = getwd(), |
|
30 |
+ folder = "glimma-plots", |
|
31 |
+ html = "MD-Plot", |
|
32 |
+ launch = TRUE, |
|
33 |
+ ... |
|
34 |
+) |
|
17 | 35 |
} |
18 | 36 |
\arguments{ |
19 | 37 |
\item{x}{the data.frame object containing expression and fold change values.} |
... | ... |
@@ -4,10 +4,20 @@ |
4 | 4 |
\alias{glMDSPlot.DESeqDataSet} |
5 | 5 |
\title{Glimma MDS Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDSPlot}{DESeqDataSet}(x, top = 500, labels = NULL, |
|
8 |
- groups = NULL, gene.selection = c("pairwise", "common"), |
|
9 |
- prior.count = 0.25, main = "MDS Plot", path = getwd(), |
|
10 |
- folder = "glimma-plots", html = "MDS-Plot", launch = TRUE, ...) |
|
7 |
+\method{glMDSPlot}{DESeqDataSet}( |
|
8 |
+ x, |
|
9 |
+ top = 500, |
|
10 |
+ labels = NULL, |
|
11 |
+ groups = NULL, |
|
12 |
+ gene.selection = c("pairwise", "common"), |
|
13 |
+ prior.count = 0.25, |
|
14 |
+ main = "MDS Plot", |
|
15 |
+ path = getwd(), |
|
16 |
+ folder = "glimma-plots", |
|
17 |
+ html = "MDS-Plot", |
|
18 |
+ launch = TRUE, |
|
19 |
+ ... |
|
20 |
+) |
|
11 | 21 |
} |
12 | 22 |
\arguments{ |
13 | 23 |
\item{x}{the DESeqDataSet containing the gene expressions.} |
... | ... |
@@ -4,10 +4,20 @@ |
4 | 4 |
\alias{glMDSPlot.DGEList} |
5 | 5 |
\title{Glimma MDS Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDSPlot}{DGEList}(x, top = 500, labels = NULL, |
|
8 |
- groups = rep(1, ncol(x)), gene.selection = c("pairwise", "common"), |
|
9 |
- prior.count = 0.25, main = "MDS Plot", path = getwd(), |
|
10 |
- folder = "glimma-plots", html = "MDS-Plot", launch = TRUE, ...) |
|
7 |
+\method{glMDSPlot}{DGEList}( |
|
8 |
+ x, |
|
9 |
+ top = 500, |
|
10 |
+ labels = NULL, |
|
11 |
+ groups = rep(1, ncol(x)), |
|
12 |
+ gene.selection = c("pairwise", "common"), |
|
13 |
+ prior.count = 2, |
|
14 |
+ main = "MDS Plot", |
|
15 |
+ path = getwd(), |
|
16 |
+ folder = "glimma-plots", |
|
17 |
+ html = "MDS-Plot", |
|
18 |
+ launch = TRUE, |
|
19 |
+ ... |
|
20 |
+) |
|
11 | 21 |
} |
12 | 22 |
\arguments{ |
13 | 23 |
\item{x}{the DGEList containing the gene expressions.} |
... | ... |
@@ -4,10 +4,19 @@ |
4 | 4 |
\alias{glMDSPlot.default} |
5 | 5 |
\title{Glimma MDS Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glMDSPlot}{default}(x, top = 500, labels = seq_cols(x), |
|
8 |
- groups = rep(1, ncol(x)), gene.selection = c("pairwise", "common"), |
|
9 |
- main = "MDS Plot", path = getwd(), folder = "glimma-plots", |
|
10 |
- html = "MDS-Plot", launch = TRUE, ...) |
|
7 |
+\method{glMDSPlot}{default}( |
|
8 |
+ x, |
|
9 |
+ top = 500, |
|
10 |
+ labels = seq_cols(x), |
|
11 |
+ groups = rep(1, ncol(x)), |
|
12 |
+ gene.selection = c("pairwise", "common"), |
|
13 |
+ main = "MDS Plot", |
|
14 |
+ path = getwd(), |
|
15 |
+ folder = "glimma-plots", |
|
16 |
+ html = "MDS-Plot", |
|
17 |
+ launch = TRUE, |
|
18 |
+ ... |
|
19 |
+) |
|
11 | 20 |
} |
12 | 21 |
\arguments{ |
13 | 22 |
\item{x}{the matrix containing the gene expressions.} |
... | ... |
@@ -4,13 +4,35 @@ |
4 | 4 |
\alias{glScatter.default} |
5 | 5 |
\title{Glimma Scatter Plot} |
6 | 6 |
\usage{ |
7 |
-\method{glScatter}{default}(x, xval = "x", yval = "y", idval = NULL, |
|
8 |
- point.size = 2, x.jitter = 0, y.jitter = 0, ndigits = NULL, |
|
9 |
- signif = 6, log = "", xgrid = FALSE, ygrid = FALSE, |
|
10 |
- xstep = FALSE, ystep = FALSE, xlab = xval, ylab = yval, |
|
11 |
- main = NULL, height = 400, width = 500, colval = NULL, |
|
12 |
- annot = c(xval, yval), annot.lab = NULL, flag = NULL, |
|
13 |
- info = NULL, hide = FALSE, disable = NULL, ...) |
|
7 |
+\method{glScatter}{default}( |
|
8 |
+ x, |
|
9 |
+ xval = "x", |
|
10 |
+ yval = "y", |
|
11 |
+ idval = NULL, |
|
12 |
+ point.size = 2, |
|
13 |
+ x.jitter = 0, |
|
14 |
+ y.jitter = 0, |
|
15 |
+ ndigits = NULL, |
|
16 |
+ signif = 6, |
|
17 |
+ log = "", |
|
18 |
+ xgrid = FALSE, |
|
19 |
+ ygrid = FALSE, |
|
20 |
+ xstep = FALSE, |
|
21 |
+ ystep = FALSE, |
|
22 |
+ xlab = xval, |
|
23 |
+ ylab = yval, |
|
24 |
+ main = NULL, |
|
25 |
+ height = 400, |
|
26 |
+ width = 500, |
|
27 |
+ colval = NULL, |
|
28 |
+ annot = c(xval, yval), |
|
29 |
+ annot.lab = NULL, |
|
30 |
+ flag = NULL, |
|
31 |
+ info = NULL, |
|
32 |
+ hide = FALSE, |
|
33 |
+ disable = NULL, |
|
34 |
+ ... |
|
35 |
+) |
|
14 | 36 |
} |
15 | 37 |
\arguments{ |
16 | 38 |
\item{x}{the data.frame containing data to plot.} |
... | ... |
@@ -4,13 +4,29 @@ |
4 | 4 |
\alias{glXYPlot} |
5 | 5 |
\title{Glimma XY Plot} |
6 | 6 |
\usage{ |
7 |
-glXYPlot(x, y, counts = NULL, groups = NULL, samples = NULL, |
|
8 |
- status = rep(0, nrow(data)), anno = NULL, display.columns = NULL, |
|
9 |
- xlab = "x", ylab = "y", side.main = "GeneID", |
|
10 |
- side.xlab = "Group", side.ylab = "Expression", |
|
11 |
- sample.cols = rep("#1f77b4", length(groups)), cols = c("#00bfff", |
|
12 |
- "#858585", "#ff3030"), jitter = 30, path = getwd(), |
|
13 |
- folder = "glimma-plots", html = "XY-Plot", launch = TRUE, ...) |
|
7 |
+glXYPlot( |
|
8 |
+ x, |
|
9 |
+ y, |
|
10 |
+ counts = NULL, |
|
11 |
+ groups = NULL, |
|
12 |
+ samples = NULL, |
|
13 |
+ status = rep(0, nrow(data)), |
|
14 |
+ anno = NULL, |
|
15 |
+ display.columns = NULL, |
|
16 |
+ xlab = "x", |
|
17 |
+ ylab = "y", |
|
18 |
+ side.main = "GeneID", |
|
19 |
+ side.xlab = "Group", |
|
20 |
+ side.ylab = "Expression", |
|
21 |
+ sample.cols = rep("#1f77b4", length(groups)), |
|
22 |
+ cols = c("#00bfff", "#858585", "#ff3030"), |
|
23 |
+ jitter = 30, |
|
24 |
+ path = getwd(), |
|
25 |
+ folder = "glimma-plots", |
|
26 |
+ html = "XY-Plot", |
|
27 |
+ launch = TRUE, |
|
28 |
+ ... |
|
29 |
+) |
|
14 | 30 |
} |
15 | 31 |
\arguments{ |
16 | 32 |
\item{x}{a numeric vector of values to plot on the x-axis of the summary plot.} |
... | ... |
@@ -4,9 +4,15 @@ |
4 | 4 |
\alias{glimma} |
5 | 5 |
\title{Glimma plot manager} |
6 | 6 |
\usage{ |
7 |
-glimma(..., layout = c(1, 1), path = getwd(), |
|
8 |
- folder = "glimma-plots", html = "index", overwrite = TRUE, |
|
9 |
- launch = TRUE) |
|
7 |
+glimma( |
|
8 |
+ ..., |
|
9 |
+ layout = c(1, 1), |
|
10 |
+ path = getwd(), |
|
11 |
+ folder = "glimma-plots", |
|
12 |
+ html = "index", |
|
13 |
+ overwrite = TRUE, |
|
14 |
+ launch = TRUE |
|
15 |
+) |
|
10 | 16 |
} |
11 | 17 |
\arguments{ |
12 | 18 |
\item{...}{the jschart or jslink objects for processing.} |
... | ... |
@@ -4,8 +4,15 @@ |
4 | 4 |
\alias{gllink} |
5 | 5 |
\title{Plot linkages} |
6 | 6 |
\usage{ |
7 |
-gllink(from, to, src = "none", dest = "none", flag = "none", |
|
8 |
- both = FALSE, info = "none") |
|
7 |
+gllink( |
|
8 |
+ from, |
|
9 |
+ to, |
|
10 |
+ src = "none", |
|
11 |
+ dest = "none", |
|
12 |
+ flag = "none", |
|
13 |
+ both = FALSE, |
|
14 |
+ info = "none" |
|
15 |
+) |
|
9 | 16 |
} |
10 | 17 |
\arguments{ |
11 | 18 |
\item{from}{the index of the plot from which the event is dispatched.} |
... | ... |
@@ -4,8 +4,7 @@ |
4 | 4 |
\alias{makeJson.data.frame} |
5 | 5 |
\title{JSON converter for data frames} |
6 | 6 |
\usage{ |
7 |
-\method{makeJson}{data.frame}(df, convert.logical = TRUE, |
|
8 |
- dataframe = c("rows", "columns")) |
|
7 |
+\method{makeJson}{data.frame}(df, convert.logical = TRUE, dataframe = c("rows", "columns")) |
|
9 | 8 |
} |
10 | 9 |
\arguments{ |
11 | 10 |
\item{df}{the data.frame to be converted into JSON} |
... | ... |
@@ -17,12 +17,10 @@ test_that("hex colour tools are correct", { |
17 | 17 |
expect_warning(as.hexcol(0)) |
18 | 18 |
expect_equal(as.hexcol(1), "#000000") |
19 | 19 |
|
20 |
- # R changed default palette in 4.0.0 |
|
21 |
- Rver <- with(R.Version(), paste(major, minor, sep = ".")) |
|
22 |
- post_4.0 <- compareVersion(Rver, "4.0.0") >= 0 |
|
23 |
- if (post_4.0) { |
|
24 |
- expect_equal(as.hexcol(2), "#df536b") |
|
25 |
- } else { |
|
20 |
+ # R4.0.0 changed palette |
|
21 |
+ if (getRversion() < "4.0.0") { |
|
26 | 22 |
expect_equal(as.hexcol(2), "#ff0000") |
23 |
+ } else { |
|
24 |
+ expect_equal(as.hexcol(2), "#df536b") |
|
27 | 25 |
} |
28 | 26 |
}) |