Mercurial > repos > yhoogstrate > edger_with_design_matrix
annotate edgeR_Differential_Gene_Expression.xml @ 89:875f080136b6 draft
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
author | yhoogstrate |
---|---|
date | Wed, 28 Jan 2015 09:22:54 -0500 |
parents | b2738b4d7c8c |
children | f87938c392bf |
rev | line source |
---|---|
25 | 1 <?xml version="1.0" encoding="UTF-8"?> |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
2 <tool id="edger_dge" name="edgeR: Differential Gene(Expression) Analysis" version="3.0.3-latest.b"> |
25 | 3 <description>RNA-Seq gene expression analysis using edgeR (R package)</description> |
4 | |
5 <requirements> | |
62 | 6 <!--<requirement type="package" version="3.0.1">package_r3_withx</requirement>--> |
67 | 7 <!--<requirement type="package" version="3.1.0">R</requirement>--> |
8 <requirement type="package" version="3.0.3">R</requirement> | |
77 | 9 <requirement type="package" version="latest">biocLite_edgeR_limma</requirement> |
72 | 10 <requirement type="package" version="1.3.18">graphicsmagick</requirement> |
25 | 11 </requirements> |
12 | |
79 | 13 <version_command>R --vanilla --slave -e "library(edgeR) ; cat(sessionInfo()\$otherPkgs\$edgeR\$Version)" 2> /dev/null</version_command> |
14 | |
25 | 15 <command> |
16 <!-- | |
17 The following script is written in the "Cheetah" language: | |
18 http://www.cheetahtemplate.org/docs/users_guide_html_multipage/contents.html | |
19 --> | |
20 | |
21 R --vanilla --slave -f $R_script '--args | |
22 $expression_matrix | |
23 $design_matrix | |
24 $contrast | |
25 | |
26 $fdr | |
27 | |
28 $output_count_edgeR | |
29 $output_cpm | |
30 | |
31 /dev/null <!-- Calculation of FPKM/RPKM should come here --> | |
32 | |
33 #if $output_raw_counts: | |
34 $output_raw_counts | |
35 #else: | |
36 /dev/null | |
37 #end if | |
38 | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
39 #if $output_MDSplot_logFC: |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
40 $output_MDSplot_logFC |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
41 #else: |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
42 /dev/null |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
43 #end if |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
44 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
45 #if $output_MDSplot_bcv: |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
46 $output_MDSplot_bcv |
25 | 47 #else: |
48 /dev/null | |
49 #end if | |
50 | |
51 #if $output_BCVplot: | |
52 $output_BCVplot | |
53 #else: | |
54 /dev/null | |
55 #end if | |
56 | |
57 #if $output_MAplot: | |
58 $output_MAplot | |
59 #else: | |
60 /dev/null | |
61 #end if | |
62 | |
63 #if $output_PValue_distribution_plot: | |
64 $output_PValue_distribution_plot | |
65 #else: | |
66 /dev/null | |
67 #end if | |
68 | |
69 #if $output_hierarchical_clustering_plot: | |
70 $output_hierarchical_clustering_plot | |
71 #else: | |
72 /dev/null | |
73 #end if | |
74 | |
75 #if $output_heatmap_plot: | |
76 $output_heatmap_plot | |
77 #else: | |
78 /dev/null | |
79 #end if | |
80 | |
81 #if $output_RData_obj: | |
82 $output_RData_obj | |
83 #else: | |
84 /dev/null | |
85 #end if | |
55 | 86 |
87 $output_format_images | |
88 ' | |
25 | 89 #if $output_R: |
90 > $output_R | |
91 #else: | |
92 > /dev/null | |
93 #end if | |
94 | |
53 | 95 2> stderr.txt ; |
96 | |
70 | 97 #if $output_format_images.value == "png": |
98 echo "Converting PDF figures to PNG" ; | |
69 | 99 |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
100 #if $output_MDSplot_logFC: |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
101 #set $output_MDSplot_logFC_tmp = str($output_MDSplot_logFC)+".png" |
70 | 102 |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
103 gm convert $output_MDSplot_logFC $output_MDSplot_logFC_tmp ; |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
104 mv $output_MDSplot_logFC_tmp $output_MDSplot_logFC ; |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
105 #end if |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
106 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
107 #if $output_MDSplot_bcv: |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
108 #set $output_MDSplot_bcv_tmp = str($output_MDSplot_bcv)+".png" |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
109 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
110 gm convert $output_MDSplot_bcv $output_MDSplot_bcv_tmp ; |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
111 mv $output_MDSplot_bcv_tmp $output_MDSplot_bcv ; |
70 | 112 #end if |
113 | |
114 #if $output_BCVplot: | |
115 #set $output_BCVplot_tmp = str($output_BCVplot)+".png" | |
116 | |
72 | 117 gm convert $output_BCVplot $output_BCVplot_tmp ; |
70 | 118 mv $output_BCVplot_tmp $output_BCVplot ; |
119 #end if | |
69 | 120 |
70 | 121 #if $output_MAplot: |
122 #set $output_MAplot_tmp = str($output_MAplot)+".png" | |
123 | |
72 | 124 gm convert $output_MAplot $output_MAplot_tmp ; |
70 | 125 mv $output_MAplot_tmp $output_MAplot ; |
126 #end if | |
127 | |
128 #if $output_PValue_distribution_plot: | |
129 #set $output_PValue_distribution_plot_tmp = str($output_PValue_distribution_plot)+".png" | |
130 | |
72 | 131 gm convert $output_PValue_distribution_plot $output_PValue_distribution_plot_tmp ; |
70 | 132 mv $output_PValue_distribution_plot_tmp $output_PValue_distribution_plot ; |
133 #end if | |
69 | 134 |
70 | 135 #if $output_hierarchical_clustering_plot: |
136 #set $output_hierarchical_clustering_plot_tmp = str($output_hierarchical_clustering_plot)+".png" | |
137 | |
72 | 138 gm convert $output_hierarchical_clustering_plot $output_hierarchical_clustering_plot_tmp ; |
70 | 139 mv $output_hierarchical_clustering_plot_tmp $output_hierarchical_clustering_plot ; |
140 #end if | |
141 | |
142 #if $output_heatmap_plot: | |
143 #set $output_heatmap_plot_tmp = str($output_heatmap_plot)+".png" | |
144 | |
72 | 145 gm convert $output_heatmap_plot $output_heatmap_plot_tmp ; |
70 | 146 mv $output_heatmap_plot_tmp $output_heatmap_plot ; |
147 #end if | |
67 | 148 #end if |
149 | |
53 | 150 grep -v 'Calculating library sizes from column' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; |
151 | |
152 ## Locale error messages: | |
153 grep -v 'During startup - Warning messages' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
154 grep -v 'Setting LC_TIME failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
155 grep -v 'Setting LC_MONETARY failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
156 grep -v 'Setting LC_PAPER failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
157 grep -v 'Setting LC_MEASUREMENT failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
158 grep -v 'Setting LC_CTYPE failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
159 grep -v 'Setting LC_COLLATE failed' stderr.txt > stderr2.txt ; rm stderr.txt ; mv stderr2.txt stderr.txt ; | |
160 | |
161 cat stderr.txt >&2 | |
25 | 162 </command> |
163 | |
164 <inputs> | |
165 <param name="expression_matrix" type="data" format="tabular" label="Expression (read count) matrix" /> | |
166 <param name="design_matrix" type="data" format="tabular" label="Design matrix" hepl="Ensure your samplenames are identical to those in the expression matrix. Preferentially, create the contrast matrix using 'edgeR: Design- from Expression matrix'." /> | |
167 | |
168 <param name="contrast" type="text" label="Contrast (biological question)" help="e.g. 'tumor-normal' or '(G1+G2)/2-G3' using the factors chosen in the design matrix. Read the 'makeContrasts' manual from Limma package for more info: http://www.bioconductor.org/packages/release/bioc/html/limma.html and http://www.bioconductor.org/packages/release/bioc/vignettes/limma/inst/doc/usersguide.pdf." /> | |
169 | |
170 <param name="fdr" type="float" min="0" max="1" value="0.05" label="False Discovery Rate (FDR)" /> | |
171 | |
172 <param name="outputs" type="select" label="Optional desired outputs" multiple="true" display="checkboxes"> | |
173 <option value="make_output_raw_counts">Raw counts table</option> | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
174 <option value="make_output_MDSplot_logFC">MDS-plot (logFC-method)</option> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
175 <option value="make_output_MDSplot_bcv">MDS-plot (BCV-method; much slower)</option> |
25 | 176 <option value="make_output_BCVplot">BCV-plot</option> |
177 <option value="make_output_MAplot">MA-plot</option> | |
178 <option value="make_output_PValue_distribution_plot">P-Value distribution plot</option> | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
179 <option value="make_output_hierarchical_clustering_plot">Hierarchical custering (under contstruction)</option> |
25 | 180 <option value="make_output_heatmap_plot">Heatmap</option> |
181 | |
43 | 182 <option value="make_output_R_stdout">R stdout</option> |
25 | 183 <option value="make_output_RData_obj">R Data object</option> |
184 </param> | |
55 | 185 |
186 <param name="output_format_images" type="select" label="Output format of images" display="radio"> | |
187 <option value="png">Portable network graphics (.png)</option> | |
188 <option value="pdf">Portable document format (.pdf)</option> | |
189 <option value="svg">Scalable vector graphics (.svg)</option> | |
190 </param> | |
25 | 191 </inputs> |
192 | |
193 <configfiles> | |
194 <configfile name="R_script"> | |
195 library(limma,quietly=TRUE) ## enable quietly to avoid unnecessaity stderr dumping | |
196 library(edgeR,quietly=TRUE) ## enable quietly to avoid unnecessaity stderr dumping | |
197 library(splines,quietly=TRUE) ## enable quietly to avoid unnecessaity stderr dumping | |
198 | |
199 ## Fetch commandline arguments | |
200 args <- commandArgs(trailingOnly = TRUE) | |
201 | |
202 expression_matrix_file = args[1] | |
203 design_matrix_file = args[2] | |
204 contrast = args[3] | |
205 | |
206 fdr = args[4] | |
207 | |
208 output_count_edgeR = args[5] | |
209 output_cpm = args[6] | |
210 | |
43 | 211 output_xpkm = args[7] ##FPKM file - yet to be implemented |
25 | 212 |
213 output_raw_counts = args[8] | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
214 output_MDSplot_logFC = args[9] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
215 output_MDSplot_bcv = args[10] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
216 output_BCVplot = args[11] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
217 output_MAplot = args[12] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
218 output_PValue_distribution_plot = args[13] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
219 output_hierarchical_clustering_plot = args[14] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
220 output_heatmap_plot = args[15] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
221 output_RData_obj = args[16] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
222 output_format_images = args[17] |
25 | 223 |
224 | |
225 library(edgeR) | |
226 ##raw_data <- read.delim(designmatrix,header=T,stringsAsFactors=T) | |
227 ## Obtain read-counts | |
228 | |
229 expression_matrix <- read.delim(expression_matrix_file,header=T,stringsAsFactors=F,row.names=1,check.names=FALSE,na.strings=c("")) | |
230 design_matrix <- read.delim(design_matrix_file,header=T,stringsAsFactors=F,row.names=1,check.names=FALSE,na.strings=c("")) | |
231 | |
232 colnames(design_matrix) <- make.names(colnames(design_matrix)) | |
233 | |
234 for(i in 1:ncol(design_matrix)) { | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
235 old <- design_matrix[,i] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
236 design_matrix[,i] <- make.names(design_matrix[,i]) |
25 | 237 if(paste(design_matrix[,i],collapse="\t") != paste(old,collapse="\t")) { |
238 print("Renaming of factors:") | |
239 print(old) | |
240 print("To:") | |
241 print(design_matrix[,i]) | |
242 } | |
45 | 243 ## The following line seems to malfunction the script: |
244 ##design_matrix[,i] <- as.factor(design_matrix[,i]) | |
25 | 245 } |
246 | |
44 | 247 ## 1) In the expression matrix, you only want to have the samples described in the design matrix |
25 | 248 columns <- match(rownames(design_matrix),colnames(expression_matrix)) |
43 | 249 columns <- columns[!is.na(columns)] |
25 | 250 read_counts <- expression_matrix[,columns] |
251 | |
44 | 252 ## 2) In the design matrix, you only want to have samples of which you really have the counts |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
253 columns <- match(colnames(read_counts),rownames(design_matrix)) |
44 | 254 columns <- columns[!is.na(columns)] |
255 design_matrix <- design_matrix[columns,,drop=FALSE] | |
25 | 256 |
257 ## Filter for HTSeq predifined counts: | |
258 exclude_HTSeq <- c("no_feature","ambiguous","too_low_aQual","not_aligned","alignment_not_unique") | |
259 exclude_DEXSeq <- c("_ambiguous","_empty","_lowaqual","_notaligned") | |
260 | |
44 | 261 exclude <- match(c(exclude_HTSeq, exclude_DEXSeq),rownames(read_counts)) |
262 exclude <- exclude[is.na(exclude)==0] | |
25 | 263 if(length(exclude) != 0) { |
44 | 264 read_counts <- read_counts[-exclude,] |
25 | 265 } |
266 | |
267 | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
268 ## sorting expression matrix with the order of the read_counts |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
269 ##order <- match(colnames(read_counts) , rownames(design_matrix)) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
270 ##read_counts_ordered <- read_counts[,order2] |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
271 |
44 | 272 empty_samples <- apply(read_counts,2,function(x) sum(x) == 0) |
25 | 273 if(sum(empty_samples) > 0) { |
274 write(paste("There are ",sum(empty_samples)," empty samples found:",sep=""),stderr()) | |
275 write(colnames(read_counts)[empty_samples],stderr()) | |
276 } else { | |
277 | |
278 dge <- DGEList(counts=read_counts,genes=rownames(read_counts)) | |
279 | |
280 formula <- paste(c("~0",make.names(colnames(design_matrix))),collapse = " + ") | |
281 design_matrix_tmp <- design_matrix | |
282 colnames(design_matrix_tmp) <- make.names(colnames(design_matrix_tmp)) | |
283 design <- model.matrix(as.formula(formula),design_matrix_tmp) | |
284 rm(design_matrix_tmp) | |
285 | |
286 # Filter prefixes | |
287 prefixes = colnames(design_matrix)[attr(design,"assign")] | |
288 avoid = nchar(prefixes) == nchar(colnames(design)) | |
289 replacements = substr(colnames(design),nchar(prefixes)+1,nchar(colnames(design))) | |
290 replacements[avoid] = colnames(design)[avoid] | |
291 colnames(design) = replacements | |
292 | |
293 # Do normalization | |
294 write("Calculating normalization factors...",stdout()) | |
295 dge <- calcNormFactors(dge) | |
296 write("Estimating common dispersion...",stdout()) | |
297 dge <- estimateGLMCommonDisp(dge,design) | |
298 write("Estimating trended dispersion...",stdout()) | |
299 dge <- estimateGLMTrendedDisp(dge,design) | |
300 write("Estimating tagwise dispersion...",stdout()) | |
301 dge <- estimateGLMTagwiseDisp(dge,design) | |
302 | |
303 | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
304 if(output_MDSplot_logFC != "/dev/null") { |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
305 write("Creating MDS plot (logFC method)",stdout()) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
306 points <- plotMDS.DGEList(dge,top=500,labels=rep("",nrow(dge\$samples)))# Get coordinates of unflexible plot |
25 | 307 dev.off()# Kill it |
308 | |
67 | 309 if(output_format_images == "pdf" || output_format_images == "png") { |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
310 pdf(output_MDSplot_logFC,height=14,width=14) |
55 | 311 } else if(output_format_images == "svg") { |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
312 svg(output_MDSplot_logFC,height=14,width=14) |
70 | 313 } |
314 ## else { | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
315 ## png(output_MDSplot_logFC) |
67 | 316 ##} |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
317 ## png does not work out of the box in the Galaxy Toolshed Version of R due to its compile settings |
55 | 318 |
25 | 319 diff_x <- abs(max(points\$x)-min(points\$x)) |
320 diff_y <-(max(points\$y)-min(points\$y)) | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
321 plot(c(min(points\$x),max(points\$x) + 0.45 * diff_x), c(min(points\$y) - 0.05 * diff_y,max(points\$y) + 0.05 * diff_y), main="edgeR logFC-MDS Plot on top 500 genes",type="n", xlab="Leading logFC dim 1", ylab="Leading logFC dim 2") |
25 | 322 points(points\$x,points\$y,pch=20) |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
323 text(points\$x, points\$y,rownames(dge\$samples),cex=1.25,col="gray",pos=4) |
25 | 324 rm(diff_x,diff_y) |
325 | |
326 dev.off() | |
327 } | |
328 | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
329 if(output_MDSplot_bcv != "/dev/null") { |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
330 write("Creating MDS plot (bcv method)",stdout()) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
331 pdf("/home/youri/Desktop/bcvmds.pdf") |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
332 points <- plotMDS.DGEList(dge,method="bcv",top=500,labels=rep("",nrow(dge\$samples)))# Get coordinates of unflexible plot |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
333 dev.off()# Kill it |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
334 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
335 if(output_format_images == "pdf" || output_format_images == "png") { |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
336 pdf(output_MDSplot_bcv,height=14,width=14) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
337 } else if(output_format_images == "svg") { |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
338 svg(output_MDSplot_bcv,height=14,width=14) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
339 } |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
340 ## else { |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
341 ## png(output_MDSplot_bcv) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
342 ##} |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
343 ## png does not work out of the box in the Galaxy Toolshed Version of R due to its compile settings |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
344 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
345 diff_x <- abs(max(points\$x)-min(points\$x)) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
346 diff_y <-(max(points\$y)-min(points\$y)) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
347 plot(c(min(points\$x),max(points\$x) + 0.45 * diff_x), c(min(points\$y) - 0.05 * diff_y,max(points\$y) + 0.05 * diff_y), main="edgeR BCV-MDS Plot",type="n", xlab="Leading BCV dim 1", ylab="Leading BCV dim 2") |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
348 points(points\$x,points\$y,pch=20) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
349 text(points\$x, points\$y,rownames(dge\$samples),cex=1.25,col="gray",pos=4) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
350 rm(diff_x,diff_y) |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
351 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
352 dev.off() |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
353 } |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
354 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
355 |
25 | 356 if(output_BCVplot != "/dev/null") { |
357 write("Creating Biological coefficient of variation plot",stdout()) | |
60 | 358 |
67 | 359 if(output_format_images == "pdf" || output_format_images == "png") { |
60 | 360 pdf(output_BCVplot) |
361 } else if(output_format_images == "svg") { | |
362 svg(output_BCVplot) | |
70 | 363 } |
364 ##else { | |
67 | 365 ## png(output_BCVplot) |
366 ##} | |
60 | 367 |
25 | 368 plotBCV(dge, cex=0.4, main="edgeR: Biological coefficient of variation (BCV) vs abundance") |
369 dev.off() | |
370 } | |
371 | |
372 | |
373 write("Fitting GLM...",stdout()) | |
374 fit <- glmFit(dge,design) | |
375 | |
376 write(paste("Performing likelihood ratio test: ",contrast,sep=""),stdout()) | |
377 cont <- c(contrast) | |
378 cont <- makeContrasts(contrasts=cont, levels=design) | |
379 | |
380 lrt <- glmLRT(fit, contrast=cont[,1]) | |
381 write(paste("Exporting to file: ",output_count_edgeR,sep=""),stdout()) | |
382 write.table(file=output_count_edgeR,topTags(lrt,n=nrow(read_counts))\$table,sep="\t",row.names=TRUE,col.names=NA) | |
383 write.table(file=output_cpm,cpm(dge,normalized.lib.sizes=TRUE),sep="\t",row.names=TRUE,col.names=NA) | |
384 | |
385 ## todo EXPORT FPKM | |
386 write.table(file=output_raw_counts,dge\$counts,sep="\t",row.names=TRUE,col.names=NA) | |
387 | |
34 | 388 if(output_MAplot != "/dev/null" || output_PValue_distribution_plot != "/dev/null") { |
25 | 389 etable <- topTags(lrt, n=nrow(dge))\$table |
390 etable <- etable[order(etable\$FDR), ] | |
32 | 391 |
392 if(output_MAplot != "/dev/null") { | |
393 write("Creating MA plot...",stdout()) | |
60 | 394 |
67 | 395 if(output_format_images == "pdf" || output_format_images == "png") { |
60 | 396 pdf(output_MAplot) |
397 } else if(output_format_images == "svg") { | |
398 svg(output_MAplot) | |
70 | 399 } |
400 ##else { | |
67 | 401 ## png(output_MAplot) |
402 ##} | |
60 | 403 |
32 | 404 with(etable, plot(logCPM, logFC, pch=20, main="edgeR: Fold change vs abundance")) |
405 with(subset(etable, FDR < fdr), points(logCPM, logFC, pch=20, col="red")) | |
406 abline(h=c(-1,1), col="blue") | |
407 dev.off() | |
408 } | |
25 | 409 |
32 | 410 if(output_PValue_distribution_plot != "/dev/null") { |
411 write("Creating P-value distribution plot...",stdout()) | |
60 | 412 |
67 | 413 if(output_format_images == "pdf" || output_format_images == "png") { |
60 | 414 pdf(output_PValue_distribution_plot) |
415 } else if(output_format_images == "svg") { | |
416 svg(output_PValue_distribution_plot) | |
70 | 417 } |
418 ##else { | |
67 | 419 ## png(output_PValue_distribution_plot) |
420 ##} | |
60 | 421 |
32 | 422 expressed_genes <- subset(etable, PValue < 0.99) |
423 h <- hist(expressed_genes\$PValue,breaks=nrow(expressed_genes)/15,main="Binned P-Values (< 0.99)") | |
424 center <- sum(h\$counts) / length(h\$counts) | |
425 lines(c(0,1),c(center,center),lty=2,col="red",lwd=2) | |
426 k <- ksmooth(h\$mid, h\$counts) | |
427 lines(k\$x,k\$y,col="red",lwd=2) | |
428 rmsd <- (h\$counts) - center | |
429 rmsd <- rmsd^2 | |
430 rmsd <- sum(rmsd) | |
431 rmsd <- sqrt(rmsd) | |
432 text(0,max(h\$counts),paste("e=",round(rmsd,2),sep=""),pos=4,col="blue") | |
433 ## change e into epsilon somehow | |
434 dev.off() | |
435 } | |
40 | 436 } |
437 | |
438 if(output_heatmap_plot != "/dev/null") { | |
60 | 439 |
67 | 440 if(output_format_images == "pdf" || output_format_images == "png") { |
60 | 441 pdf(output_heatmap_plot,width=10.5) |
442 } else if(output_format_images == "svg") { | |
443 svg(output_heatmap_plot,width=10.5) | |
70 | 444 } |
445 ## else { | |
67 | 446 ## png(output_heatmap_plot,width=10.5) |
447 ##} | |
60 | 448 |
40 | 449 etable2 <- topTags(lrt, n=100)\$table |
450 order <- rownames(etable2) | |
451 cpm_sub <- cpm(dge,normalized.lib.sizes=TRUE,log=TRUE)[as.numeric(order),] | |
452 heatmap(t(cpm_sub)) | |
453 dev.off() | |
25 | 454 } |
455 | |
456 ##output_hierarchical_clustering_plot = args[13] | |
457 | |
35 | 458 if(output_RData_obj != "/dev/null") { |
25 | 459 save.image(output_RData_obj) |
460 } | |
461 | |
462 write("Done!",stdout()) | |
463 } | |
464 </configfile> | |
465 </configfiles> | |
466 | |
467 <outputs> | |
53 | 468 <data format="tabular" name="output_count_edgeR" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - differentially expressed genes" /> |
25 | 469 <data format="tabular" name="output_cpm" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - CPM" /> |
470 | |
471 <data format="tabular" name="output_raw_counts" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - raw counts"> | |
53 | 472 <filter>outputs and ("make_output_raw_counts" in outputs)</filter> |
25 | 473 </data> |
474 | |
89
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
475 <data format="png" name="output_MDSplot_logFC" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - MDS-plot (logFC method)"> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
476 <filter>outputs and ("make_output_MDSplot_logFC" in outputs)</filter> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
477 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
478 <change_format> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
479 <when input="output_format_images" value="png" format="png" /> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
480 <when input="output_format_images" value="pdf" format="pdf" /> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
481 <when input="output_format_images" value="svg" format="svg" /> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
482 </change_format> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
483 </data> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
484 |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
485 <data format="png" name="output_MDSplot_bcv" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - MDS-plot (bcv method)"> |
875f080136b6
Solved a very serious bug: if contrast and design matrix described samples not in the same order, statistical analysis goes wrong
yhoogstrate
parents:
83
diff
changeset
|
486 <filter>outputs and ("make_output_MDSplot_bcv" in outputs)</filter> |
59 | 487 |
488 <change_format> | |
489 <when input="output_format_images" value="png" format="png" /> | |
490 <when input="output_format_images" value="pdf" format="pdf" /> | |
491 <when input="output_format_images" value="svg" format="svg" /> | |
492 </change_format> | |
25 | 493 </data> |
494 | |
60 | 495 <data format="png" name="output_BCVplot" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - BCV-plot"> |
53 | 496 <filter>outputs and ("make_output_BCVplot" in outputs)</filter> |
60 | 497 |
498 <change_format> | |
499 <when input="output_format_images" value="png" format="png" /> | |
500 <when input="output_format_images" value="pdf" format="pdf" /> | |
501 <when input="output_format_images" value="svg" format="svg" /> | |
502 </change_format> | |
25 | 503 </data> |
504 | |
60 | 505 <data format="png" name="output_MAplot" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - MA-plot"> |
53 | 506 <filter>outputs and ("make_output_MAplot" in outputs)</filter> |
60 | 507 |
508 <change_format> | |
509 <when input="output_format_images" value="png" format="png" /> | |
510 <when input="output_format_images" value="pdf" format="pdf" /> | |
511 <when input="output_format_images" value="svg" format="svg" /> | |
512 </change_format> | |
25 | 513 </data> |
514 | |
60 | 515 <data format="png" name="output_PValue_distribution_plot" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - P-Value distribution"> |
53 | 516 <filter>outputs and ("make_output_PValue_distribution_plot" in outputs)</filter> |
60 | 517 |
518 <change_format> | |
519 <when input="output_format_images" value="png" format="png" /> | |
520 <when input="output_format_images" value="pdf" format="pdf" /> | |
521 <when input="output_format_images" value="svg" format="svg" /> | |
522 </change_format> | |
25 | 523 </data> |
524 | |
60 | 525 <data format="png" name="output_hierarchical_clustering_plot" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - Hierarchical custering"> |
53 | 526 <filter>outputs and ("make_output_hierarchical_clustering_plot" in outputs)</filter> |
60 | 527 |
528 <change_format> | |
529 <when input="output_format_images" value="png" format="png" /> | |
530 <when input="output_format_images" value="pdf" format="pdf" /> | |
531 <when input="output_format_images" value="svg" format="svg" /> | |
532 </change_format> | |
25 | 533 </data> |
534 | |
60 | 535 <data format="png" name="output_heatmap_plot" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - Heatmap"> |
53 | 536 <filter>outputs and ("make_output_heatmap_plot" in outputs)</filter> |
60 | 537 |
538 <change_format> | |
539 <when input="output_format_images" value="png" format="png" /> | |
540 <when input="output_format_images" value="pdf" format="pdf" /> | |
541 <when input="output_format_images" value="svg" format="svg" /> | |
542 </change_format> | |
25 | 543 </data> |
544 | |
545 <data format="RData" name="output_RData_obj" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - R data object"> | |
53 | 546 <filter>outputs and ("make_output_RData_obj" in outputs)</filter> |
25 | 547 </data> |
548 | |
40 | 549 <data format="txt" name="output_R" label="edgeR DGE on ${design_matrix.hid}: ${design_matrix.name} - R output (debug)" > |
53 | 550 <filter>outputs and ("make_output_R_stdout" in outputs)</filter> |
25 | 551 </data> |
552 </outputs> | |
553 | |
554 <help> | |
555 edgeR: Differential Gene(Expression) Analysis | |
36 | 556 ############################################# |
25 | 557 |
36 | 558 Overview |
559 -------- | |
560 Differential expression analysis of RNA-seq and digital gene expression profiles with biological replication. Uses empirical Bayes estimation and exact tests based on the negative binomial distribution. Also useful for differential signal analysis with other types of genome-scale count data [1]. | |
25 | 561 |
562 For every experiment, the algorithm requires a design matrix. This matrix describes which samples belong to which groups. | |
36 | 563 More details on this are given in the edgeR manual: http://www.bioconductor.org/packages/2.12/bioc/vignettes/edgeR/inst/doc/edgeRUsersGuide.pdf |
25 | 564 and the limma manual. |
565 | |
566 Because the creation of a design matrix can be complex and time consuming, especially if no GUI is used, this package comes with an alternative tool which can help you with it. | |
567 This tool is called *edgeR Design Matrix Creator*. | |
568 If the appropriate design matrix (with corresponding links to the files) is given, | |
569 the correct contrast ( http://en.wikipedia.org/wiki/Contrast_(statistics) ) has to be given. | |
570 | |
571 If you have for example two groups, with an equal weight, you would like to compare either | |
79 | 572 "g1-g2" or "normal-cancer". |
25 | 573 |
36 | 574 The test function makes use of a MCF7 dataset used in a study that indicates that a higher sequencing depth is not neccesairily more important than a higher amount of replaciates[2]. |
25 | 575 |
36 | 576 Input |
577 ----- | |
578 Expression matrix | |
579 ^^^^^^^^^^^^^^^^^ | |
580 :: | |
25 | 581 |
582 Geneid "\t" Sample-1 "\t" Sample-2 "\t" Sample-3 "\t" Sample-4 [...] "\n" | |
583 SMURF "\t" 123 "\t" 21 "\t" 34545 "\t" 98 ... "\n" | |
584 BRCA1 "\t" 435 "\t" 6655 "\t" 45 "\t" 55 ... "\n" | |
585 LINK33 "\t" 4 "\t" 645 "\t" 345 "\t" 1 ... "\n" | |
586 SNORD78 "\t" 498 "\t" 65 "\t" 98 "\t" 27 ... "\n" | |
587 [...] | |
588 | |
36 | 589 *Note: Make sure the number of columns in the header is identical to the number of columns in the body.* |
25 | 590 |
36 | 591 Design matrix |
592 ^^^^^^^^^^^^^ | |
593 :: | |
25 | 594 |
595 Sample "\t" Condition "\t" Ethnicity "\t" Patient "\t" Batch "\n" | |
596 Sample-1 "\t" Tumor "\t" European "\t" 1 "\t" 1 "\n" | |
597 Sample-2 "\t" Normal "\t" European "\t" 1 "\t" 1 "\n" | |
598 Sample-3 "\t" Tumor "\t" European "\t" 2 "\t" 1 "\n" | |
599 Sample-4 "\t" Normal "\t" European "\t" 2 "\t" 1 "\n" | |
600 Sample-5 "\t" Tumor "\t" African "\t" 3 "\t" 1 "\n" | |
601 Sample-6 "\t" Normal "\t" African "\t" 3 "\t" 1 "\n" | |
602 Sample-7 "\t" Tumor "\t" African "\t" 4 "\t" 2 "\n" | |
603 Sample-8 "\t" Normal "\t" African "\t" 4 "\t" 2 "\n" | |
604 Sample-9 "\t" Tumor "\t" Asian "\t" 5 "\t" 2 "\n" | |
605 Sample-10 "\t" Normal "\t" Asian "\t" 5 "\t" 2 "\n" | |
606 Sample-11 "\t" Tumor "\t" Asian "\t" 6 "\t" 2 "\n" | |
607 Sample-12 "\t" Normal "\t" Asian "\t" 6 "\t" 2 "\n" | |
608 | |
36 | 609 *Note: Avoid factor names that are (1) numerical, (2) contain mathematical symbols and preferebly only use letters.* |
25 | 610 |
36 | 611 Contrast |
612 ^^^^^^^^ | |
613 The contrast represents the biological question. There can be many questions asked, e.g.: | |
25 | 614 |
36 | 615 - Tumor-Normal |
616 - African-European | |
617 - 0.5*(Control+Placebo) / Treated | |
25 | 618 |
36 | 619 Installation |
620 ------------ | |
25 | 621 |
622 This tool requires no specific configurations. The following dependencies are installed automatically: | |
36 | 623 |
624 - R | |
625 - Bioconductor | |
79 | 626 - limma |
627 - edgeR | |
25 | 628 |
36 | 629 License |
630 ------- | |
631 - R | |
79 | 632 - GPL 2 & GPL 3 |
36 | 633 - limma |
634 - GPL (>=2) | |
635 - edgeR | |
79 | 636 - GPL (>=2) |
36 | 637 |
638 References | |
639 ---------- | |
640 | |
641 EdgeR | |
642 ^^^^^ | |
643 **[1] edgeR: a Bioconductor package for differential expression analysis of digital gene expression data.** | |
25 | 644 |
36 | 645 *Mark D. Robinson, Davis J. McCarthy and Gordon K. Smyth* - Bioinformatics (2010) 26 (1): 139-140. |
646 | |
647 - http://www.bioconductor.org/packages/2.12/bioc/html/edgeR.html | |
648 - http://dx.doi.org/10.1093/bioinformatics/btp616 | |
649 - http://www.bioconductor.org/packages/release/bioc/html/edgeR.html | |
25 | 650 |
36 | 651 Test-data (MCF7) |
652 ^^^^^^^^^^^^^^^^ | |
653 **[2] RNA-seq differential expression studies: more sequence or more replication?** | |
654 | |
655 *Yuwen Liu, Jie Zhou and Kevin P. White* - Bioinformatics (2014) 30 (3): 301-304. | |
656 | |
657 - http://www.ncbi.nlm.nih.gov/pubmed/24319002 | |
658 - http://dx.doi.org/10.1093/bioinformatics/btt688 | |
659 | |
660 Contact | |
661 ------- | |
79 | 662 |
663 The tool wrapper has been written by Youri Hoogstrate from the Erasmus | |
664 Medical Center (Rotterdam, Netherlands) on behalf of the Translational | |
665 Research IT (TraIT) project: | |
83 | 666 |
25 | 667 http://www.ctmm.nl/en/programmas/infrastructuren/traitprojecttranslationeleresearch |
668 | |
79 | 669 More tools by the Translational Research IT (TraIT) project can be found |
670 in the following toolsheds: | |
83 | 671 |
672 http://toolshed.dtls.nl/ | |
673 | |
674 http://toolshed.g2.bx.psu.edu | |
675 | |
676 http://testtoolshed.g2.bx.psu.edu/ | |
79 | 677 |
36 | 678 I would like to thank Hina Riaz - Naz Khan for her helpful contribution. |
25 | 679 </help> |
680 </tool> |