comparison small_rna_maps.r @ 11:a561a71bd7d7 draft

planemo upload for repository https://github.com/ARTbio/tools-artbio/tree/master/tools/small_rna_maps commit c24bbb6d53574eb1c1eb8d219cf2a39a9ed5b3ff
author artbio
date Tue, 06 Mar 2018 06:11:55 -0500
parents a96e6a7df2b7
children d33263e6e812
comparison
equal deleted inserted replaced
10:c3fb2a864526 11:a561a71bd7d7
41 for (sample in samples) { 41 for (sample in samples) {
42 Table[, length(Table)][Table$Dataset==sample] <- Table[, length(Table)][Table$Dataset==sample]*norm_factors[i] 42 Table[, length(Table)][Table$Dataset==sample] <- Table[, length(Table)][Table$Dataset==sample]*norm_factors[i]
43 i = i + 1 43 i = i + 1
44 } 44 }
45 } 45 }
46 genes=unique(levels(Table$Chromosome)) 46 genes=unique(Table$Chromosome)
47 per_gene_readmap=lapply(genes, function(x) subset(Table, Chromosome==x)) 47 per_gene_readmap=lapply(genes, function(x) subset(Table, Chromosome==x))
48 per_gene_limit=lapply(genes, function(x) c(1, unique(subset(Table, Chromosome==x)$Chrom_length)) ) 48 per_gene_limit=lapply(genes, function(x) c(1, unique(subset(Table, Chromosome==x)$Chrom_length)) )
49 n_genes=length(per_gene_readmap) 49 n_genes=length(per_gene_readmap)
50 # second table 50 # second table
51 if (args$extra_plot_method != '') { 51 if (args$extra_plot_method != '') {
145 ...) 145 ...)
146 } 146 }
147 combineLimits(p) 147 combineLimits(p)
148 } 148 }
149 149
150 plot_single <- function(df, method=args$first_plot_method, rows_per_page=rows_per_page, ...) {
151 if (method == 'Counts') {
152 p = xyplot(Counts~Coordinate|factor(Dataset, levels=unique(Dataset))+factor(Chromosome, levels=unique(Chromosome)),
153 data=df,
154 type='h',
155 lwd=1.5,
156 scales= list(relation="free", x=list(rot=0, cex=0.7, axs="i", tck=0.5), y=list(tick.number=4, rot=90, cex=0.7)),
157 xlab=list(label=bottom_first_method[[args$first_plot_method]], cex=.85),
158 ylab=list(label=legend_first_method[[args$first_plot_method]], cex=.85),
159 main=title_first_method[[args$first_plot_method]],
160 origin = 0,
161 group=Polarity,
162 col=c("red","blue"),
163 par.strip.text = list(cex=0.7),
164 as.table=T,
165 ...)
166 p = update(useOuterStrips(p, strip.left=strip.custom(par.strip.text = list(cex=0.5))), layout=c(n_samples, rows_per_page))
167 return(p)
168 } else if (method != "Size") {
169 p = xyplot(eval(as.name(method))~Coordinate|factor(Dataset, levels=unique(Dataset))+factor(Chromosome, levels=unique(Chromosome)),
170 data=df,
171 type='p',
172 pch=19,
173 cex=0.35,
174 scales= list(relation="free", x=list(rot=0, cex=0.7, axs="i", tck=0.5), y=list(tick.number=4, rot=90, cex=0.7)),
175 xlab=list(label=bottom_first_method[[args$first_plot_method]], cex=.85),
176 ylab=list(label=legend_first_method[[args$first_plot_method]], cex=.85),
177 main=title_first_method[[args$first_plot_method]],
178 origin = 0,
179 group=Polarity,
180 col=c("red","blue"),
181 par.strip.text = list(cex=0.7),
182 as.table=T,
183 ...)
184 p = update(useOuterStrips(p, strip.left=strip.custom(par.strip.text = list(cex=0.5))), layout=c(n_samples, rows_per_page))
185 return(p)
186 } else {
187 p= barchart(Counts~as.factor(Size)|factor(Dataset, levels=unique(Dataset))+Chromosome, data = df, origin = 0,
188 horizontal=FALSE,
189 group=Polarity,
190 stack=TRUE,
191 col=c('red', 'blue'),
192 scales=list(y=list(tick.number=4, rot=90, relation="free", cex=0.5, alternating=T), x=list(rot=0, cex=0.6, tck=0.5, alternating=c(3,3))),
193 xlab=list(label=bottom_first_method[[args$first_plot_method]], cex=.85),
194 ylab=list(label=legend_first_method[[args$first_plot_method]], cex=.85),
195 main=title_first_method[[args$first_plot_method]],
196 par.strip.text = list(cex=0.7),
197 nrow = 8,
198 as.table=TRUE,
199 ...)
200 p = update(useOuterStrips(p, strip.left=strip.custom(par.strip.text = list(cex=0.5))), layout=c(n_samples, rows_per_page))
201 p = combineLimits(p, extend=TRUE)
202 return (p)
203 }
204 }
205
206 ## function parameters 150 ## function parameters
207 151
208 #par.settings.firstplot = list(layout.heights=list(top.padding=11, bottom.padding = -14)) 152 #par.settings.firstplot = list(layout.heights=list(top.padding=11, bottom.padding = -14))
209 #par.settings.secondplot=list(layout.heights=list(top.padding=11, bottom.padding = -15), strip.background=list(col=c("lavender","deepskyblue"))) 153 #par.settings.secondplot=list(layout.heights=list(top.padding=11, bottom.padding = -15), strip.background=list(col=c("lavender","deepskyblue")))
210 par.settings.firstplot = list(layout.heights=list(top.padding=-2, bottom.padding=-2)) 154 par.settings.firstplot = list(layout.heights=list(top.padding=-2, bottom.padding=-2))
218 bottom_extra_method =list(Counts="Coordinates (nbre of bases)",Coverage="Coordinates (nbre of bases)", Median="Coordinates (nbre of bases)", Mean="Coordinates (nbre of bases)", Size="Sizes of reads") 162 bottom_extra_method =list(Counts="Coordinates (nbre of bases)",Coverage="Coordinates (nbre of bases)", Median="Coordinates (nbre of bases)", Mean="Coordinates (nbre of bases)", Size="Sizes of reads")
219 163
220 ## Plotting Functions 164 ## Plotting Functions
221 165
222 double_plot <- function(...) { 166 double_plot <- function(...) {
223 if (n_genes > 5) {page_height=15; rows_per_page=10} else { 167 page_height = 15
224 rows_per_page= 2 * n_genes; page_height=1.5*n_genes} 168 rows_per_page = 10
225 if (n_samples > 4) {page_width = 8.2677*n_samples/4} else {page_width = 7 * n_samples/2} 169 graph_heights=c(40,30,40,30,40,30,40,30,40,30,10)
170 if (n_samples > 4) {page_width = 8.2677*n_samples/4} else {page_width = 2.3*n_samples +2.5}
226 pdf(file=args$output_pdf, paper="special", height=page_height, width=page_width) 171 pdf(file=args$output_pdf, paper="special", height=page_height, width=page_width)
227 for (i in seq(1,n_genes,rows_per_page/2)) { 172 for (i in seq(1,n_genes,rows_per_page/2)) {
228 start=i 173 start=i
229 end=i+rows_per_page/2-1 174 end=i+rows_per_page/2-1
230 if (end>n_genes) {end=n_genes} 175 if (end>n_genes) {end=n_genes}
176 if (end-start+1 < 5) {graph_heights=c(rep(c(40,30),end-start+1),10,rep(c(40,30),5-(end-start+1)))}
231 first_plot.list = lapply(per_gene_readmap[start:end], function(x) plot_unit(x, strip=FALSE, par.settings=par.settings.firstplot)) 177 first_plot.list = lapply(per_gene_readmap[start:end], function(x) plot_unit(x, strip=FALSE, par.settings=par.settings.firstplot))
232 second_plot.list = lapply(per_gene_size[start:end], function(x) plot_unit(x, method=args$extra_plot_method, par.settings=par.settings.secondplot)) 178 second_plot.list = lapply(per_gene_size[start:end], function(x) plot_unit(x, method=args$extra_plot_method, par.settings=par.settings.secondplot))
233 plot.list=rbind(second_plot.list, first_plot.list) 179 plot.list=rbind(second_plot.list, first_plot.list)
234 args_list=c(plot.list, list( nrow=rows_per_page+1, ncol=1, heights=unit(c(40,30,40,30,40,30,40,30,40,30,10), rep("mm", 11)), 180 args_list=c(plot.list, list( nrow=rows_per_page+1, ncol=1, heights=unit(graph_heights, rep("mm", 11)),
235 top=textGrob(paste(title_first_method[[args$first_plot_method]], "and", title_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), vjust=0, just="top"), 181 top=textGrob(paste(title_first_method[[args$first_plot_method]], "and", title_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), vjust=0, just="top"),
236 left=textGrob(paste(legend_first_method[[args$first_plot_method]], "/", legend_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), vjust=2, rot=90), 182 left=textGrob(paste(legend_first_method[[args$first_plot_method]], "/", legend_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), just=0.675*(end-start-(2.2*(4/2.7))),vjust=2, rot=90),
237 sub=textGrob(paste(bottom_first_method[[args$first_plot_method]], "/", bottom_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), just="bottom", vjust=2) 183 sub=textGrob(paste(bottom_first_method[[args$first_plot_method]], "/", bottom_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), just="bottom", vjust=2)
238 ) 184 )
239 ) 185 )
240 do.call(grid.arrange, args_list) 186 do.call(grid.arrange, args_list)
241 } 187 }
244 190
245 191
246 single_plot <- function(...) { 192 single_plot <- function(...) {
247 width = 8.2677 * n_samples / 2 193 width = 8.2677 * n_samples / 2
248 rows_per_page=8 194 rows_per_page=8
249 pdf(file=args$output_pdf, paper="special", height=11.69, width=width) 195 graph_heights=c(rep(40,8),10)
196 pdf(file=args$output_pdf, paper="special", height=15, width=width)
250 for (i in seq(1,n_genes,rows_per_page)) { 197 for (i in seq(1,n_genes,rows_per_page)) {
251 start=i 198 start=i
252 end=i+rows_per_page-1 199 end=i+rows_per_page-1
253 if (end>n_genes) {end=n_genes} 200 if (end>n_genes) {end=n_genes}
254 bunch = do.call(rbind, per_gene_readmap[start:end]) # sub dataframe from the list 201 if (end-start+1 < 8) {graph_heights=c(rep(c(40),end-start+1),10,rep(c(40),8-(end-start+1)))}
255 p = plot_single(bunch, method=args$first_plot_method, par.settings=par.settings.single_plot, rows_per_page=rows_per_page) 202 first_plot.list = lapply(per_gene_readmap[start:end], function(x) plot_unit(x, par.settings=par.settings.firstplot))
256 plot(p) 203 plot.list=rbind(first_plot.list)
204 args_list=c(plot.list, list( nrow=rows_per_page+1, ncol=1, heights=unit(graph_heights, rep("mm", 9)),
205 top=textGrob(title_first_method[[args$first_plot_method]], gp=gpar(cex=1), vjust=0, just="top"),
206 left=textGrob(legend_first_method[[args$first_plot_method]], gp=gpar(cex=1), just=(6.4/7)*(end-start-(6.2*(7/6.4))),vjust=2, rot=90),
207 sub=textGrob(bottom_first_method[[args$first_plot_method]], gp=gpar(cex=1), just="bottom", vjust=2)
208 )
209 )
210 do.call(grid.arrange, args_list)
257 } 211 }
258 devname=dev.off() 212 devname=dev.off()
259 } 213 }
260 214
261 # main 215 # main