Skip to content
Snippets Groups Projects
Commit 8c0070d8 authored by Hugo  VARET's avatar Hugo VARET
Browse files

ggplot3.3.0

parent dfdba078
No related branches found
No related tags found
No related merge requests found
......@@ -2,10 +2,10 @@ Package: ChIPuanaR
Type: Package
Title: Differential analysis of ChIP-Seq data
Version: 0.99.0
Date: 2020-04-06
Date: 2020-05-07
Author: Marie-Agnes Dillies, Hugo Varet and Maëlle Daunesse
Maintainer: Maëlle Daunesse <maelle.daunesse@pasteur.fr>
Depends: R (>= 3.4.0), DESeq2, limma, kableExtra, knitr, ggplot2
Depends: R (>= 3.4.0), DESeq2, limma, kableExtra, knitr, ggplot2 (>= 3.3.0)
Imports: stats, utils, graphics, ggrepel, grDevices, grid, ggdendro, gridExtra, rmarkdown (>= 1.4), SummarizedExperiment, S4Vectors, scales
biocViews: Software
VignetteBuilder: knitr
......@@ -15,4 +15,4 @@ Description: Provide R tools and an environment for the differential
perform statistical analysis/testing with DESeq2 or limma, export
results and create final report.
License: GPL-2
RoxygenNote: 7.0.0
RoxygenNote: 7.1.0
......@@ -33,7 +33,7 @@ MAPlot <- function(results, method, alpha=0.05, outfile=FALSE, log2FClim=NULL){
scale_colour_manual(values=c("no"="black", "yes"="red"), drop=FALSE) +
scale_shape_manual(values=c("bottom"=25, "in"=21, "top"=24), drop=FALSE) +
scale_fill_manual(values=c("no"="black", "yes"="red"), drop=FALSE) +
scale_y_continuous(expand=expand_scale(mult=c(0.03, 0.03))) +
scale_y_continuous(expand=expansion(mult=c(0.03, 0.03))) +
ylab(expression(log[2]~fold~change)) +
ggtitle(paste0("MA-plot - ", gsub("_"," ",name)))
if (method=="DESeq2"){
......
......@@ -21,7 +21,7 @@ barplotTotal <- function(counts, conditions,
scale_fill_manual(values=col) +
xlab("Samples") +
ylab("Total read count (million)") +
scale_y_continuous(expand=expand_scale(mult=c(0.01, 0.05))) +
scale_y_continuous(expand=expansion(mult=c(0.01, 0.05))) +
ggtitle("Total read count per sample (million)") +
theme(axis.text.x=element_text(angle=90, hjust=1, vjust=0.5)))
if (outfile) dev.off()
......
......@@ -18,6 +18,6 @@ clusterPlot <- function(counts.trans, conditions, outfile=FALSE){
ggtitle("Cluster dendrogram\nEuclidean distance, Ward criterion") +
theme(axis.text.x=element_text(angle=90, hjust=1, vjust=0.5),
axis.text.y=element_text(angle=0)) +
scale_y_continuous(expand=expand_scale(mult=c(0.01, 0.05))))
scale_y_continuous(expand=expansion(mult=c(0.01, 0.05))))
if (outfile) dev.off()
}
......@@ -17,7 +17,7 @@ rawpHist <- function(result, outfile=FALSE){
result.name <- result[[name]]
p[[name]] <- ggplot(data=result.name, aes(x=.data$pvalue)) +
geom_histogram(color="white", breaks=seq(0, 1, by=0.025)) +
scale_y_continuous(expand=expand_scale(mult=c(0.01, 0.05))) +
scale_y_continuous(expand=expansion(mult=c(0.01, 0.05))) +
xlab("Raw p-value") +
ylab("Frequency") +
ggtitle(paste0("Distribution of raw p-values - ", gsub("_"," ",name)))
......
......@@ -13,5 +13,4 @@ To install the ChIPuanaR package from GitLab, open a R session and:
- Some users may have to install the pandoc and pandoc-citeproc libraries to be able to generate the final HTML reports
- For Windows users only, install [Rtools](https://cran.r-project.org/bin/windows/Rtools/) or check that it is already installed (needed to build the package)
- Load the devtools R package with `library(devtools)`
- Run `install_gitlab(repo="hub/chipuanar", host="gitlab.pasteur.fr", build_vignettes=TRUE)`
- Run `devtools::install_gitlab(repo="hub/chipuanar", host="gitlab.pasteur.fr", build_vignettes=TRUE)`
......@@ -47,6 +47,7 @@ if (method=="Limma") {
colnames(sf) <- "Size factor"
}
counts.trans <- resAnDif$voom$E
colnames(counts.trans) <- gsub("^norm.", "", colnames(counts.trans))
############### DESeq2 ########################################
} else if(method=="DESeq2") {
library(DESeq2)
......@@ -226,21 +227,15 @@ A p-value adjustment is performed to take into account multiple testing and cont
```{r echo=FALSE, results="asis"}
df <- matrix(NA, ncol = 3, nrow = length(resAnDif$results),
dimnames=list(names(resAnDif$result), c("Total peaks", "Peaks up", "Peaks down")))
for (name in names(resAnDif$results)) {
results.name <- resAnDif$results[[name]]
# Total number of peaks
peaks <- as.integer(nrow(results.name[which(results.name$padj<=alpha),]))
#Nb gene up
peaks.up <- as.integer(nrow(results.name[which(results.name$padj<=alpha & results.name$log2FoldChange>0),]))
#Nb gene down
peaks.down <-as.integer(nrow(results.name[which(results.name$padj<=alpha & results.name$log2FoldChange<0),]))
df[name,] <- c(peaks, peaks.up, peaks.down)
peaks.up <- nrow(results.name[which(results.name$padj <= alpha & results.name$log2FoldChange > 0),])
peaks.down <- nrow(results.name[which(results.name$padj <= alpha & results.name$log2FoldChange < 0),])
df[name,] <- c(peaks.up+peaks.down, peaks.up, peaks.down)
}
kable(df, caption = "Table 4: Normalization factors",format = "html") %>%
kable_styling(c("striped", "bordered", "responsive"), font_size = 14) %>%
column_spec(1, bold = T)
column_spec(1, bold = TRUE)
```
Figure 8 represents the MA-plot of the data for the comparisons done, where differentially expressed features are highlighted in red. A MA-plot represents the log ratio of differential expression as a function of the mean intensity for each feature. Triangles correspond to features having a too low/high $\log_2(\text{FC})$ to be displayed on the plot.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment