Skip to content

Commit

Permalink
Merge pull request #41 from PF2-pasteur-fr/development
Browse files Browse the repository at this point in the history
Development
  • Loading branch information
hvaret authored Mar 20, 2018
2 parents 73a5514 + 20b2980 commit 4ddef16
Show file tree
Hide file tree
Showing 16 changed files with 86 additions and 22 deletions.
5 changes: 3 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
Package: SARTools
Type: Package
Title: Statistical Analysis of RNA-Seq Tools
Version: 1.6.0
Date: 2017-12-11
Version: 1.6.1
Date: 2018-03-20
Author: Marie-Agnes Dillies and Hugo Varet
Maintainer: Hugo Varet <[email protected]>
Depends: R (>= 3.3.0), DESeq2 (>= 1.12.0), edgeR (>= 3.12.0), xtable
Expand All @@ -12,3 +12,4 @@ VignetteBuilder: knitr
Encoding: latin1
Description: Provide R tools and an environment for the statistical analysis of RNA-Seq projects: load and clean data, produce figures, perform statistical analysis/testing with DESeq2 or edgeR, export results and create final report.
License: GPL-2
RoxygenNote: 6.0.1
5 changes: 5 additions & 0 deletions NEWS
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
CHANGES IN VERSION 1.6.1
------------------------
o new boolean parameter forceCairoGraph
o adapt size of PNG plots if width/height are too large

CHANGES IN VERSION 1.6.0
------------------------
o use "percentage" instead of "proportion" in some plots
Expand Down
2 changes: 1 addition & 1 deletion R/MAPlot.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
MAPlot <- function(complete, alpha=0.05, outfile=TRUE){
ncol <- ifelse(length(complete)<=4, ceiling(sqrt(length(complete))), 3)
nrow <- ceiling(length(complete)/ncol)
if (outfile) png(filename="figures/MAPlot.png", width=1800*ncol, height=1800*nrow, res=300)
if (outfile) png(filename="figures/MAPlot.png", width=cairoSizeWrapper(1800*ncol), height=cairoSizeWrapper(1800*nrow), res=300)
par(mfrow=c(nrow,ncol))
for (name in names(complete)){
complete.name <- complete[[name]]
Expand Down
2 changes: 1 addition & 1 deletion R/PCAPlot.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ PCAPlot <- function(counts.trans, group, n=min(500,nrow(counts.trans)),
prp <- round(prp[1:3],2)

# create figure
if (outfile) png(filename="figures/PCA.png",width=1800*2,height=1800,res=300)
if (outfile) png(filename="figures/PCA.png",width=cairoSizeWrapper(1800*2),height=cairoSizeWrapper(1800),res=300)
par(mfrow=c(1,2))
# axes 1 et 2
abs=range(pca$x[,1]); abs=abs(abs[2]-abs[1])/25;
Expand Down
16 changes: 16 additions & 0 deletions R/cairoSizeWrapper.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
#' Cairo Size Wrapper
#'
#' Limits the pixel size to either to the minimum of the given and the max allowed pixel size 32767x32767 pixels if
#' Cairo graphical has been choosen
#'
#' @param pixel_re requested pixel size
#' @return the minimum between the requested and maximal allowed pixel size if Cairo is selected otherwise the requested pixel size
#' @author vipul patel

cairoSizeWrapper <- function(pixel_re){
if (options("bitmapType") == "cairo"){
return(min(pixel_re,32767))
} else{
return(pixel_re)
}
}
2 changes: 1 addition & 1 deletion R/diagSizeFactorsPlots.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ diagSizeFactorsPlots <- function(dds, group, col=c("lightblue","orange","MediumV
if ("diag" %in% plots){
ncol <- ifelse(ncol(counts(dds))<=4, ceiling(sqrt(ncol(counts(dds)))), 3)
nrow <- ceiling(ncol(counts(dds))/ncol)
if (outfile) png(filename="figures/diagSizeFactorsHist.png", width=1400*ncol, height=1400*nrow, res=300)
if (outfile) png(filename="figures/diagSizeFactorsHist.png", width=cairoSizeWrapper(1400*ncol), height=cairoSizeWrapper(1400*nrow), res=300)
par(mfrow=c(nrow,ncol))
geomeans <- exp(rowMeans(log(counts(dds))))
samples <- colnames(counts(dds))
Expand Down
2 changes: 1 addition & 1 deletion R/pairwiseScatterPlots.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
pairwiseScatterPlots <- function(counts, group, outfile=TRUE){
ncol <- ncol(counts)
if (ncol <= 30){
if (outfile) png(filename="figures/pairwiseScatter.png", width=700*ncol, height=700*ncol, res=300)
if (outfile) png(filename="figures/pairwiseScatter.png", width=cairoSizeWrapper(700*ncol), height=cairoSizeWrapper(700*ncol), res=300)
# defining panel and lower.panel functions
panel <- function(x,y,...){points(x, y, pch=".");abline(a=0,b=1,lty=2);}
lower.panel <- function(x,y,...){
Expand Down
2 changes: 1 addition & 1 deletion R/rawpHist.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
rawpHist <- function(complete, outfile=TRUE){
ncol <- ifelse(length(complete)<=4, ceiling(sqrt(length(complete))), 3)
nrow <- ceiling(length(complete)/ncol)
if (outfile) png(filename="figures/rawpHist.png", width=1800*ncol, height=1800*nrow, res=300)
if (outfile) png(filename="figures/rawpHist.png", width=cairoSizeWrapper(1800*ncol), height=cairoSizeWrapper(1800*nrow), res=300)
par(mfrow=c(nrow,ncol))
for (name in names(complete)){
hist(complete[[name]][,"pvalue"], nclass=50, xlab="Raw p-value",
Expand Down
2 changes: 1 addition & 1 deletion R/volcanoPlot.r
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
volcanoPlot <- function(complete, alpha=0.05, outfile=TRUE){
ncol <- ifelse(length(complete)<=4, ceiling(sqrt(length(complete))), 3)
nrow <- ceiling(length(complete)/ncol)
if (outfile) png(filename="figures/volcanoPlot.png", width=1800*ncol, height=1800*nrow, res=300)
if (outfile) png(filename="figures/volcanoPlot.png", width=cairoSizeWrapper(1800*ncol), height=cairoSizeWrapper(1800*nrow), res=300)
par(mfrow=c(nrow,ncol))
for (name in names(complete)){
complete.name <- complete[[name]]
Expand Down
Empty file modified inst/medecine-sciences.csl
100644 → 100755
Empty file.
21 changes: 21 additions & 0 deletions man/cairoSizeWrapper.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 5 additions & 2 deletions template_script_DESeq2.r
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
################################################################################
### R script to compare several conditions with the SARTools and DESeq2 packages
### Hugo Varet
### Dec 11th, 2017
### designed to be executed with SARTools 1.6.0
### March 20th, 2018
### designed to be executed with SARTools 1.6.1
################################################################################

################################################################################
Expand Down Expand Up @@ -37,11 +37,14 @@ locfunc <- "median" # "median" (default) or "sh
colors <- c("dodgerblue","firebrick1", # vector of colors of each biological condition on the plots
"MediumVioletRed","SpringGreen")

forceCairoGraph <- FALSE

################################################################################
### running script ###
################################################################################
setwd(workDir)
library(SARTools)
if (forceCairoGraph) options(bitmapType="cairo")

# checking parameters
checkParameters.DESeq2(projectName=projectName,author=author,targetFile=targetFile,
Expand Down
16 changes: 12 additions & 4 deletions template_script_DESeq2_CL.r
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
################################################################################
### R script to compare several conditions with the SARTools and DESeq2 packages
### Hugo Varet
### Dec 11th, 2017
### designed to be executed with SARTools 1.6.0
### March 20th, 2018
### designed to be executed with SARTools 1.6.1
### run "Rscript template_script_DESeq2_CL.r --help" to get some help
################################################################################

Expand Down Expand Up @@ -89,7 +89,14 @@ make_option(c("-l", "--locfunc"),
make_option(c("-C", "--colors"),
default="dodgerblue,firebrick1,MediumVioletRed,SpringGreen,chartreuse,cyan,darkorchid,darkorange",
dest="cols",
help="colors of each biological condition on the plots\n\t\t\"col1,col2,col3,col4\"\n\t\t[default: %default]")
help="colors of each biological condition on the plots\n\t\t\"col1,col2,col3,col4\"\n\t\t[default: %default]"),

make_option(c("-g", "--forceCairoGraph"),
action="store_true",
default=FALSE,
dest="forceCairoGraph",
help="activate cairo type")

)

# now parse the command line to check which option is given and get associated values
Expand Down Expand Up @@ -117,7 +124,7 @@ pAdjustMethod <- opt$pAdjustMethod # p-value adjustment method
typeTrans <- opt$typeTrans # transformation for PCA/clustering: "VST" ou "rlog"
locfunc <- opt$locfunc # "median" (default) or "shorth" to estimate the size factors
colors <- unlist(strsplit(opt$cols, ",")) # vector of colors of each biologicial condition on the plots
forceCairoGraph <- opt$forceCairoGraph # force cairo as plotting device if enabled
# print(paste("workDir", workDir))
# print(paste("projectName", projectName))
# print(paste("author", author))
Expand All @@ -141,6 +148,7 @@ colors <- unlist(strsplit(opt$cols, ",")) # vector of colors of each
################################################################################
# setwd(workDir)
library(SARTools)
if (forceCairoGraph) options(bitmapType="cairo")

# checking parameters
problem <- checkParameters.DESeq2(projectName=projectName,author=author,targetFile=targetFile,
Expand Down
7 changes: 5 additions & 2 deletions template_script_edgeR.r
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
################################################################################
### R script to compare several conditions with the SARTools and edgeR packages
### Hugo Varet
### Dec 11th, 2017
### designed to be executed with SARTools 1.6.0
### March 20th, 2018
### designed to be executed with SARTools 1.6.1
################################################################################

################################################################################
Expand Down Expand Up @@ -35,11 +35,14 @@ normalizationMethod <- "TMM" # normalization method: "TM
colors <- c("dodgerblue","firebrick1", # vector of colors of each biological condition on the plots
"MediumVioletRed","SpringGreen")

forceCairoGraph <- FALSE

################################################################################
### running script ###
################################################################################
setwd(workDir)
library(SARTools)
if (forceCairoGraph) options(bitmapType="cairo")

# checking parameters
checkParameters.edgeR(projectName=projectName,author=author,targetFile=targetFile,
Expand Down
15 changes: 11 additions & 4 deletions template_script_edgeR_CL.r
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
################################################################################
### R script to compare several conditions with the SARTools and edgeR packages
### Hugo Varet
### Dec 11th, 2017
### designed to be executed with SARTools 1.6.0
### March 20th, 2018
### designed to be executed with SARTools 1.6.1
### run "Rscript template_script_edgeR_CL.r --help" to get some help
################################################################################

Expand Down Expand Up @@ -79,7 +79,13 @@ make_option(c("-n", "--normalizationMethod"),
make_option(c("-C", "--colors"),
default="dodgerblue,firebrick1,MediumVioletRed,SpringGreen,chartreuse,cyan,darkorchid,darkorange",
dest="cols",
help="colors of each biological condition on the plots\n\t\t\"col1,col2,col3,col4\"\n\t\t[default: %default]")
help="colors of each biological condition on the plots\n\t\t\"col1,col2,col3,col4\"\n\t\t[default: %default]"),

make_option(c("-g", "--forceCairoGraph"),
action="store_true",
default=FALSE,
dest="forceCairoGraph",
help="activate cairo type")
)

# now parse the command line to check which option is given and get associated values
Expand All @@ -105,7 +111,7 @@ gene.selection <- opt$gene.selection # selection of the features
normalizationMethod <- opt$normalizationMethod # normalization method in calcNormFactors
cpmCutoff <- opt$cpmCutoff # counts-per-million cut-off to filter low counts
colors <- unlist(strsplit(opt$cols, ",")) # vector of colors of each biologicial condition on the plots

forceCairoGraph <- opt$forceCairoGraph # force cairo as plotting device if enabled
# print(paste("workDir", workDir))
# print(paste("projectName", projectName))
# print(paste("author", author))
Expand All @@ -127,6 +133,7 @@ colors <- unlist(strsplit(opt$cols, ",")) # vector of colors of each
################################################################################
# setwd(workDir)
library(SARTools)
if (forceCairoGraph) options(bitmapType="cairo")

# checking parameters
problem <- checkParameters.edgeR(projectName=projectName,author=author,targetFile=targetFile,
Expand Down
4 changes: 2 additions & 2 deletions vignettes/SARTools.rmd
Original file line number Diff line number Diff line change
Expand Up @@ -82,8 +82,8 @@ All the parameters that can be modified by the user are at the beginning of the
- `cpmCutoff`: (if use of edgeR) counts-per-million cut-off to filter low counts (default is 1, set to 0 to disable filtering);
- `gene.selection`: (if use of edgeR) method of selection of the features for the MultiDimensional Scaling plot (`"pairwise"` by default or `common`);
- `normalizationMethod`: (if use of edgeR) normalization method in `calcNormFactors()`: `"TMM"` (default), `"RLE"` (DESeq method) or `"upperquartile"`;
- `colors`: colors used for the figures (one per biological condition), 4 are given by default.

- `colors`: colors used for the figures (one per biological condition), 4 are given by default;
- `forceCairoGraph`: `TRUE` to force the use of cairo with `options(bitmapType="cairo")` (`FALSE` by default).

All these parameters will be saved and written at the end of the HTML report in order to keep track of what has been done.

Expand Down

0 comments on commit 4ddef16

Please sign in to comment.