Mercurial > repos > artbio > small_rna_maps
comparison small_rna_maps.r @ 32:f2e7ad3058e8 draft
"planemo upload for repository https://github.com/ARTbio/tools-artbio/tree/master/tools/small_rna_maps commit 51dc6c56c7d95fc229ffee958354211cd454fd36"
author | artbio |
---|---|
date | Sun, 09 May 2021 17:11:00 +0000 |
parents | 183bf49fe77c |
children | 966bc5c46efd |
comparison
equal
deleted
inserted
replaced
31:f82badb66c34 | 32:f2e7ad3058e8 |
---|---|
1 ## Setup R error handling to go to stderr | 1 ## Setup R error handling to go to stderr |
2 options( show.error.messages=F, | 2 options(show.error.messages = F, |
3 error = function () { cat( geterrmessage(), file=stderr() ); q( "no", 1, F ) } ) | 3 error = function() { |
4 cat(geterrmessage(), file = stderr()); q("no", 1, F) | |
5 } | |
6 ) | |
4 options(warn = -1) | 7 options(warn = -1) |
5 library(RColorBrewer) | 8 library(RColorBrewer) |
6 library(lattice) | 9 library(lattice) |
7 library(latticeExtra) | 10 library(latticeExtra) |
8 library(grid) | 11 library(grid) |
9 library(gridExtra) | 12 library(gridExtra) |
10 library(optparse) | 13 library(optparse) |
11 | 14 |
12 | 15 |
13 option_list <- list( | 16 option_list <- list( |
14 make_option(c("-i", "--ymin"), type="double", help="set min ylimit. e.g. '-100.0'"), | 17 make_option(c("-i", "--ymin"), type = "double", help = "set min ylimit. e.g. '-100.0'"), |
15 make_option(c("-a", "--ymax"), type="double", help="set max ylimit. e.g. '100.0'"), | 18 make_option(c("-a", "--ymax"), type = "double", help = "set max ylimit. e.g. '100.0'"), |
16 make_option(c("-f", "--first_dataframe"), type="character", help="path to first dataframe"), | 19 make_option(c("-f", "--first_dataframe"), type = "character", help = "path to first dataframe"), |
17 make_option(c("-e", "--extra_dataframe"), type="character", help="path to additional dataframe"), | 20 make_option(c("-e", "--extra_dataframe"), type = "character", help = "path to additional dataframe"), |
18 make_option(c("-n", "--normalization"), type="character", help="space-separated normalization/size factors"), | 21 make_option(c("-n", "--normalization"), type = "character", help = "space-separated normalization/size factors"), |
19 make_option("--first_plot_method", type = "character", help="How additional data should be plotted"), | 22 make_option("--first_plot_method", type = "character", help = "How additional data should be plotted"), |
20 make_option("--extra_plot_method", type = "character", help="How additional data should be plotted"), | 23 make_option("--extra_plot_method", type = "character", help = "How additional data should be plotted"), |
21 make_option("--global", type = "character", help="data should be plotted as global size distribution"), | 24 make_option("--global", type = "character", help = "data should be plotted as global size distribution"), |
22 make_option("--output_pdf", type = "character", help="path to the pdf file with plots") | 25 make_option("--output_pdf", type = "character", help = "path to the pdf file with plots") |
23 ) | 26 ) |
24 | 27 |
25 parser <- OptionParser(usage = "%prog [options] file", option_list = option_list) | 28 parser <- OptionParser(usage = "%prog [options] file", option_list = option_list) |
26 args = parse_args(parser) | 29 args <- parse_args(parser) |
27 | 30 |
28 # data frames implementation | 31 # data frames implementation |
29 | 32 |
30 ## first table | 33 ## first table |
31 Table = read.delim(args$first_dataframe, header=T, row.names=NULL) | 34 table <- read.delim(args$first_dataframe, header = T, row.names = NULL) |
32 colnames(Table)[1] <- "Dataset" | 35 colnames(table)[1] <- "Dataset" |
33 dropcol <- c("Strandness", "z.score") # not used by this Rscript and is dropped for backward compatibility | 36 dropcol <- c("Strandness", "z.score") # not used by this Rscript and is dropped for backward compatibility |
34 Table <- Table[,!(names(Table) %in% dropcol)] | 37 table <- table[, !(names(table) %in% dropcol)] |
35 if (args$first_plot_method == "Counts" | args$first_plot_method == "Size") { | 38 if (args$first_plot_method == "Counts" | args$first_plot_method == "Size") { |
36 Table <- within(Table, Counts[Polarity=="R"] <- (Counts[Polarity=="R"]*-1)) | 39 table <- within(table, Counts[Polarity == "R"] <- (Counts[Polarity == "R"] * - 1)) |
37 } | 40 } |
38 n_samples=length(unique(Table$Dataset)) | 41 n_samples <- length(unique(table$Dataset)) |
39 samples = unique(Table$Dataset) | 42 samples <- unique(table$Dataset) |
40 if (args$normalization != "") { | 43 if (args$normalization != "") { |
41 norm_factors = as.numeric(unlist(strsplit(args$normalization, " "))) | 44 norm_factors <- as.numeric(unlist(strsplit(args$normalization, " "))) |
42 } else { | 45 } else { |
43 norm_factors = rep(1, n_samples) | 46 norm_factors <- rep(1, n_samples) |
44 } | 47 } |
45 if (args$first_plot_method == "Counts" | args$first_plot_method == "Size" | args$first_plot_method == "Coverage") { | 48 if (args$first_plot_method == "Counts" | args$first_plot_method == "Size" | args$first_plot_method == "Coverage") { |
46 i = 1 | 49 i <- 1 |
47 for (sample in samples) { | 50 for (sample in samples) { |
48 # Warning | 51 # Warning Here the column is hard coded as the last column (dangerous) |
49 # Here the column is hard coded as the last column (dangerous) | |
50 # because its name changes with the method | 52 # because its name changes with the method |
51 Table[, length(Table)][Table$Dataset==sample] <- Table[, length(Table)][Table$Dataset==sample]*norm_factors[i] | 53 table[, length(table)][table$Dataset == sample] <- table[, length(table)][table$Dataset == sample] * norm_factors[i] |
52 i = i + 1 | 54 i <- i + 1 |
53 } | 55 } |
54 } | 56 } |
55 genes=unique(Table$Chromosome) | 57 genes <- unique(table$Chromosome) |
56 per_gene_readmap=lapply(genes, function(x) subset(Table, Chromosome==x)) | 58 per_gene_readmap <- lapply(genes, function(x) subset(table, Chromosome == x)) |
57 per_gene_limit=lapply(genes, function(x) c(1, unique(subset(Table, Chromosome==x)$Chrom_length)) ) | 59 per_gene_limit <- lapply(genes, function(x) c(1, unique(subset(table, Chromosome == x)$Chrom_length))) |
58 n_genes=length(per_gene_readmap) | 60 n_genes <- length(per_gene_readmap) |
59 | 61 |
60 # second table | 62 # second table |
61 if (args$extra_plot_method != '') { | 63 if (args$extra_plot_method != "") { |
62 ExtraTable=read.delim(args$extra_dataframe, header=T, row.names=NULL) | 64 extra_table <- read.delim(args$extra_dataframe, header = T, row.names = NULL) |
63 colnames(ExtraTable)[1] <- "Dataset" | 65 colnames(extra_table)[1] <- "Dataset" |
64 dropcol <- c("Strandness", "z.score") # not used by this Rscript and is dropped for backward compatibility | 66 dropcol <- c("Strandness", "z.score") |
65 Table <- Table[,!(names(Table) %in% dropcol)] | 67 table <- table[, !(names(table) %in% dropcol)] |
66 if (args$extra_plot_method == "Counts" | args$extra_plot_method=='Size') { | 68 if (args$extra_plot_method == "Counts" | args$extra_plot_method == "Size") { |
67 ExtraTable <- within(ExtraTable, Counts[Polarity=="R"] <- (Counts[Polarity=="R"]*-1)) | 69 extra_table <- within(extra_table, Counts[Polarity == "R"] <- (Counts[Polarity == "R"] * -1)) |
68 } | 70 } |
69 if (args$extra_plot_method == "Counts" | args$extra_plot_method == "Size" | args$extra_plot_method == "Coverage") { | 71 if (args$extra_plot_method == "Counts" | args$extra_plot_method == "Size" | args$extra_plot_method == "Coverage") { |
70 i = 1 | 72 i <- 1 |
71 for (sample in samples) { | 73 for (sample in samples) { |
72 ExtraTable[, length(ExtraTable)][ExtraTable$Dataset==sample] <- ExtraTable[, length(ExtraTable)][ExtraTable$Dataset==sample]*norm_factors[i] | 74 extra_table[, length(extra_table)][extra_table$Dataset == sample] <- extra_table[, length(extra_table)][extra_table$Dataset == sample] * norm_factors[i] |
73 i = i + 1 | 75 i <- i + 1 |
74 } | 76 } |
75 } | 77 } |
76 per_gene_size=lapply(genes, function(x) subset(ExtraTable, Chromosome==x)) | 78 per_gene_size <- lapply(genes, function(x) subset(extra_table, Chromosome == x)) |
77 } | 79 } |
78 | 80 |
79 ## functions | 81 ## functions |
80 globalbc = function(df, global="", ...) { | 82 globalbc <- function(df, global = "", ...) { |
81 if (global == "yes") { | 83 if (global == "yes") { |
82 bc <- barchart(Counts~as.factor(Size)|factor(Dataset, levels=unique(Dataset)), | 84 bc <- barchart(Counts ~ as.factor(Size) | factor(Dataset, levels = unique(Dataset)), |
83 data = df, origin = 0, | 85 data = df, origin = 0, |
84 horizontal=FALSE, | 86 horizontal = FALSE, |
85 col=c("darkblue"), | 87 col = c("darkblue"), |
86 scales=list(y=list(tick.number=4, rot=90, relation="same", cex=0.5, alternating=T), x=list(rot=0, cex=0.6, tck=0.5, alternating=c(3,3))), | 88 scales = list(y = list(tick.number = 4, rot = 90, relation = "same", cex = 0.5, alternating = T), x = list(rot = 0, cex = 0.6, tck = 0.5, alternating = c(3, 3))), |
87 xlab=list(label=bottom_first_method[[args$first_plot_method]], cex=.85), | 89 xlab = list(label = bottom_first_method[[args$first_plot_method]], cex = .85), |
88 ylab=list(label=legend_first_method[[args$first_plot_method]], cex=.85), | 90 ylab = list(label = legend_first_method[[args$first_plot_method]], cex = .85), |
89 main=title_first_method[[args$first_plot_method]], | 91 main = title_first_method[[args$first_plot_method]], |
90 layout = c(2, 6), newpage=T, | 92 layout = c(2, 6), newpage = T, |
91 as.table=TRUE, | 93 as.table = TRUE, |
92 aspect=0.5, | 94 aspect = 0.5, |
93 strip = strip.custom(par.strip.text = list(cex = 1), which.given=1, bg="lightblue"), | 95 strip = strip.custom(par.strip.text = list(cex = 1), which.given = 1, bg = "lightblue"), |
94 ... | 96 ... |
95 ) | 97 ) |
96 } else { | 98 } else { |
97 bc <- barchart(Counts~as.factor(Size)|factor(Dataset, levels=unique(Dataset)), | 99 bc <- barchart(Counts ~ as.factor(Size) | factor(Dataset, levels = unique(Dataset)), |
98 data = df, origin = 0, | 100 data = df, origin = 0, |
99 horizontal=FALSE, | 101 horizontal = FALSE, |
100 group=Polarity, | 102 group = Polarity, |
101 stack=TRUE, | 103 stack = TRUE, |
102 col=c('red', 'blue'), | 104 col = c("red", "blue"), |
103 scales=list(y=list(tick.number=4, rot=90, relation="same", cex=0.5, alternating=T), x=list(rot=0, cex=0.6, tck=0.5, alternating=c(3,3))), | 105 scales = list(y = list(tick.number = 4, rot = 90, relation = "same", cex = 0.5, alternating = T), x = list(rot = 0, cex = 0.6, tck = 0.5, alternating = c(3, 3))), |
104 xlab=list(label=bottom_first_method[[args$first_plot_method]], cex=.85), | 106 xlab = list(label = bottom_first_method[[args$first_plot_method]], cex = .85), |
105 ylab=list(label=legend_first_method[[args$first_plot_method]], cex=.85), | 107 ylab = list(label = legend_first_method[[args$first_plot_method]], cex = .85), |
106 main=title_first_method[[args$first_plot_method]], | 108 main = title_first_method[[args$first_plot_method]], |
107 layout = c(2, 6), newpage=T, | 109 layout = c(2, 6), newpage = T, |
108 as.table=TRUE, | 110 as.table = TRUE, |
109 aspect=0.5, | 111 aspect = 0.5, |
110 strip = strip.custom(par.strip.text = list(cex = 1), which.given=1, bg="lightblue"), | 112 strip = strip.custom(par.strip.text = list(cex = 1), which.given = 1, bg = "lightblue"), |
111 ... | 113 ... |
112 ) | 114 ) |
113 } | 115 } |
114 return(bc) | 116 return(bc) |
115 } | 117 } |
116 plot_unit = function(df, method=args$first_plot_method, ...) { | 118 plot_unit <- function(df, method = args$first_plot_method, ...) { |
117 if (exists('ymin', where=args)){ | 119 if (exists("ymin", where = args)) { |
118 min=args$ymin | 120 min <- args$ymin |
119 }else{ | 121 } else { |
120 min='' | 122 min <- "" |
121 } | 123 } |
122 if ((exists('ymax', where=args))){ | 124 if ((exists("ymax", where = args))) { |
123 max=args$ymax | 125 max <- args$ymax |
124 }else{ | 126 } else { |
125 max='' | 127 max <- "" |
126 } | 128 } |
127 ylimits=c(min,max) | 129 ylimits <- c(min, max) |
128 if (method == 'Counts') { | 130 if (method == "Counts") { |
129 p = xyplot(Counts~Coordinate|factor(Dataset, levels=unique(Dataset))+factor(Chromosome, levels=unique(Chromosome)), | 131 p <- xyplot(Counts ~ Coordinate | factor(Dataset, levels = unique(Dataset)) + factor(Chromosome, levels = unique(Chromosome)), |
130 data=df, | 132 data = df, |
131 type='h', | 133 type = "h", |
132 lwd=1.5, | 134 lwd = 1.5, |
133 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)), | 135 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)), |
134 xlab=NULL, main=NULL, ylab=NULL, ylim=ylimits, | 136 xlab = NULL, main = NULL, ylab = NULL, ylim = ylimits, |
135 as.table=T, | 137 as.table = T, |
136 origin = 0, | 138 origin = 0, |
137 horizontal=FALSE, | 139 horizontal = FALSE, |
138 group=Polarity, | 140 group = Polarity, |
139 col=c("red","blue"), | 141 col = c("red", "blue"), |
140 par.strip.text = list(cex=0.7), | 142 par.strip.text = list(cex = 0.7), |
141 ...) | 143 ...) |
142 p=combineLimits(p) | 144 p <- combineLimits(p) |
143 } else if (method != "Size") { | 145 } else if (method != "Size") { |
144 p = xyplot(eval(as.name(method))~Coordinate|factor(Dataset, levels=unique(Dataset))+factor(Chromosome, levels=unique(Chromosome)), | 146 p <- xyplot(eval(as.name(method)) ~ Coordinate | factor(Dataset, levels = unique(Dataset)) + factor(Chromosome, levels = unique(Chromosome)), |
145 data=df, | 147 data = df, |
146 type= ifelse(method=='Coverage', 'l', 'p'), | 148 type = ifelse(method == "Coverage", "l", "p"), |
147 pch=19, | 149 pch = 19, |
148 cex=0.35, | 150 cex = 0.35, |
149 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)), | 151 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)), |
150 xlab=NULL, main=NULL, ylab=NULL, ylim=ylimits, | 152 xlab = NULL, main = NULL, ylab = NULL, ylim = ylimits, |
151 as.table=T, | 153 as.table = T, |
152 origin = 0, | 154 origin = 0, |
153 horizontal=FALSE, | 155 horizontal = FALSE, |
154 group=Polarity, | 156 group = Polarity, |
155 col=c("red","blue"), | 157 col = c("red", "blue"), |
156 par.strip.text = list(cex=0.7), | 158 par.strip.text = list(cex = 0.7), |
157 ...) | 159 ...) |
158 p=combineLimits(p) | 160 p <- combineLimits(p) |
159 } else { | 161 } else { |
160 p = barchart(Counts~as.factor(Size)|factor(Dataset, levels=unique(Dataset))+Chromosome, data = df, origin = 0, | 162 p <- barchart(Counts ~ as.factor(Size) | factor(Dataset, levels = unique(Dataset)) + Chromosome, data = df, origin = 0, |
161 horizontal=FALSE, | 163 horizontal = FALSE, |
162 group=Polarity, | 164 group = Polarity, |
163 stack=TRUE, | 165 stack = TRUE, |
164 col=c('red', 'blue'), | 166 col = c("red", "blue"), |
165 scales=list(y=list(rot=90, relation="free", cex=0.7), x=list(rot=0, cex=0.7, axs="i", tck=c(1,0))), | 167 scales = list(y = list(rot = 90, relation = "free", cex = 0.7), x = list(rot = 0, cex = 0.7, axs = "i", tck = c(1, 0))), |
166 xlab = NULL, | 168 xlab = NULL, |
167 ylab = NULL, | 169 ylab = NULL, |
168 main = NULL, | 170 main = NULL, |
169 as.table=TRUE, | 171 as.table = TRUE, |
170 par.strip.text = list(cex=0.6), | 172 par.strip.text = list(cex = 0.6), |
171 ...) | 173 ...) |
172 p=combineLimits(p) | 174 p <- combineLimits(p) |
173 } | 175 } |
174 return(p) | 176 return(p) |
175 } | 177 } |
176 | 178 |
177 | 179 |
178 ## function parameters | 180 ## function parameters |
179 | 181 |
180 #par.settings.firstplot = list(layout.heights=list(top.padding=11, bottom.padding = -14)) | 182 par_settings_firstplot <- list(layout.heights = list(top.padding = -2, bottom.padding = -2), strip.background = list(col = c("lightblue", "lightgreen"))) |
181 #par.settings.secondplot=list(layout.heights=list(top.padding=11, bottom.padding = -15), strip.background=list(col=c("lavender","deepskyblue"))) | 183 par_settings_secondplot <- list(layout.heights = list(top.padding = -1, bottom.padding = -1), strip.background = list(col = c("lightblue", "lightgreen"))) |
182 par.settings.firstplot = list(layout.heights=list(top.padding=-2, bottom.padding=-2),strip.background=list(col=c("lightblue","lightgreen"))) | 184 title_first_method <- list(Counts = "Read Counts", Coverage = "Coverage depths", Median = "Median sizes", Mean = "Mean sizes", Size = "Size Distributions") |
183 par.settings.secondplot=list(layout.heights=list(top.padding=-1, bottom.padding=-1),strip.background=list(col=c("lightblue","lightgreen"))) | 185 title_extra_method <- list(Counts = "Read Counts", Coverage = "Coverage depths", Median = "Median sizes", Mean = "Mean sizes", Size = "Size Distributions") |
184 title_first_method = list(Counts="Read Counts", Coverage="Coverage depths", Median="Median sizes", Mean="Mean sizes", Size="Size Distributions") | 186 legend_first_method <- list(Counts = "Read count", Coverage = "Coverage depth", Median = "Median size", Mean = "Mean size", Size = "Read count") |
185 title_extra_method = list(Counts="Read Counts", Coverage="Coverage depths", Median="Median sizes", Mean="Mean sizes", Size="Size Distributions") | 187 legend_extra_method <- list(Counts = "Read count", Coverage = "Coverage depth", Median = "Median size", Mean = "Mean size", Size = "Read count") |
186 legend_first_method =list(Counts="Read count", Coverage="Coverage depth", Median="Median size", Mean="Mean size", Size="Read count") | 188 bottom_first_method <- list(Counts = "Coordinates (nucleotides)", Coverage = "Coordinates (nucleotides)", Median = "Coordinates (nucleotides)", Mean = "Coordinates (nucleotides)", Size = "Sizes of reads") |
187 legend_extra_method =list(Counts="Read count", Coverage="Coverage depth", Median="Median size", Mean="Mean size", Size="Read count") | 189 bottom_extra_method <- list(Counts = "Coordinates (nucleotides)", Coverage = "Coordinates (nucleotides)", Median = "Coordinates (nucleotides)", Mean = "Coordinates (nucleotides)", Size = "Sizes of reads") |
188 bottom_first_method =list(Counts="Coordinates (nucleotides)",Coverage="Coordinates (nucleotides)", Median="Coordinates (nucleotides)", Mean="Coordinates (nucleotides)", Size="Sizes of reads") | |
189 bottom_extra_method =list(Counts="Coordinates (nucleotides)",Coverage="Coordinates (nucleotides)", Median="Coordinates (nucleotides)", Mean="Coordinates (nucleotides)", Size="Sizes of reads") | |
190 | 190 |
191 ## Plotting Functions | 191 ## Plotting Functions |
192 | 192 |
193 double_plot <- function(...) { | 193 double_plot <- function(...) { |
194 page_height = 15 | 194 page_height <- 15 |
195 rows_per_page = 10 | 195 rows_per_page <- 10 |
196 graph_heights=c(40,30,40,30,40,30,40,30,40,30,10) | 196 graph_heights <- c(40, 30, 40, 30, 40, 30, 40, 30, 40, 30, 10) |
197 page_width=8.2677 * n_samples / 2 | 197 page_width <- 8.2677 * n_samples / 2 |
198 pdf(file=args$output_pdf, paper="special", height=page_height, width=page_width) | 198 pdf(file = args$output_pdf, paper = "special", height = page_height, width = page_width) |
199 for (i in seq(1,n_genes,rows_per_page/2)) { | 199 for (i in seq(1, n_genes, rows_per_page / 2)) { |
200 start=i | 200 start <- i |
201 end=i+rows_per_page/2-1 | 201 end <- i + rows_per_page / 2 - 1 |
202 if (end>n_genes) {end=n_genes} | 202 if (end > n_genes) { |
203 if (end-start+1 < 5) {graph_heights=c(rep(c(40,30),end-start+1),10,rep(c(40,30),5-(end-start+1)))} | 203 end <- n_genes |
204 first_plot.list = lapply(per_gene_readmap[start:end], function(x) update(useOuterStrips(plot_unit(x, par.settings=par.settings.secondplot), strip.left=strip.custom(par.strip.text = list(cex=0.5))))) | 204 } |
205 second_plot.list = lapply(per_gene_size[start:end], function(x) update(useOuterStrips(plot_unit(x, method=args$extra_plot_method, par.settings=par.settings.firstplot), strip.left=strip.custom(par.strip.text = list(cex=0.5)), strip=FALSE))) | 205 if (end - start + 1 < 5) { |
206 plot.list=rbind(first_plot.list, second_plot.list) | 206 graph_heights <- c(rep(c(40, 30), end - start + 1), 10, rep(c(40, 30), 5 - (end - start + 1))) |
207 args_list=c(plot.list, list( nrow=rows_per_page+1, ncol=1, heights=unit(graph_heights, rep("mm", 11)), | 207 } |
208 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"), | 208 first_plot_list <- lapply(per_gene_readmap[start:end], function(x) update(useOuterStrips(plot_unit(x, par.settings = par_settings_secondplot), strip.left = strip.custom(par.strip.text = list(cex = 0.5))))) |
209 left=textGrob(paste(legend_first_method[[args$first_plot_method]], "/", legend_extra_method[[args$extra_plot_method]]), gp=gpar(cex=1), vjust=0, hjust=0, x=1, y=(-0.38/4)*(end-start-(3.28/0.38)), rot=90), | 209 second_plot_list <- lapply(per_gene_size[start:end], function(x) update(useOuterStrips(plot_unit(x, method = args$extra_plot_method, par.settings = par_settings_firstplot), strip.left = strip.custom(par.strip.text = list(cex = 0.5)), strip = FALSE))) |
210 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) | 210 plot.list <- rbind(first_plot_list, second_plot_list) |
211 args_list <- c(plot.list, list(nrow = rows_per_page + 1, ncol = 1, heights = unit(graph_heights, rep("mm", 11)), | |
212 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"), | |
213 left = textGrob(paste(legend_first_method[[args$first_plot_method]], "/", legend_extra_method[[args$extra_plot_method]]), gp = gpar(cex = 1), vjust = 0, hjust = 0, x = 1, y = (-0.38 / 4) * (end - start - (3.28 / 0.38)), rot = 90), | |
214 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) | |
211 ) | 215 ) |
212 ) | 216 ) |
213 do.call(grid.arrange, args_list) | 217 do.call(grid.arrange, args_list) |
214 } | 218 } |
215 devname=dev.off() | 219 devname <- dev.off() |
216 } | 220 } |
217 | 221 |
218 | 222 |
219 single_plot <- function(...) { | 223 single_plot <- function(...) { |
220 width = 8.2677 * n_samples / 2 | 224 width <- 8.2677 * n_samples / 2 |
221 rows_per_page=8 | 225 rows_per_page <- 8 |
222 graph_heights=c(rep(40,8),10) | 226 graph_heights <- c(rep(40, 8), 10) |
223 pdf(file=args$output_pdf, paper="special", height=15, width=width) | 227 pdf(file = args$output_pdf, paper = "special", height = 15, width = width) |
224 for (i in seq(1,n_genes,rows_per_page)) { | 228 for (i in seq(1, n_genes, rows_per_page)) { |
225 start=i | 229 start <- i |
226 end=i+rows_per_page-1 | 230 end <- i + rows_per_page - 1 |
227 if (end>n_genes) {end=n_genes} | 231 if (end > n_genes) { |
228 if (end-start+1 < 8) {graph_heights=c(rep(c(40),end-start+1),10,rep(c(40),8-(end-start+1)))} | 232 end <- n_genes |
229 first_plot.list = lapply(per_gene_readmap[start:end], function(x) update(useOuterStrips(plot_unit(x, par.settings=par.settings.firstplot),strip.left=strip.custom(par.strip.text = list(cex=0.5))))) | 233 } |
230 plot.list=rbind(first_plot.list) | 234 if (end - start + 1 < 8) { |
231 args_list=c(plot.list, list( nrow=rows_per_page+1, ncol=1, heights=unit(graph_heights, rep("mm", 9)), | 235 graph_heights <- c(rep(c(40), end - start + 1), 10, rep(c(40), 8 - (end - start + 1))) |
232 top=textGrob(title_first_method[[args$first_plot_method]], gp=gpar(cex=1), vjust=0, just="top"), | 236 } |
233 left=textGrob(legend_first_method[[args$first_plot_method]], gp=gpar(cex=1), vjust=0, hjust=0, x=1, y=(-0.41/7)*(end-start-(6.23/0.41)), rot=90), | 237 first_plot_list <- lapply(per_gene_readmap[start:end], function(x) update(useOuterStrips(plot_unit(x, par.settings = par_settings_firstplot), strip.left = strip.custom(par.strip.text = list(cex = 0.5))))) |
234 sub=textGrob(bottom_first_method[[args$first_plot_method]], gp=gpar(cex=1), just="bottom", vjust=2) | 238 plot.list <- rbind(first_plot_list) |
239 args_list <- c(plot.list, list(nrow = rows_per_page + 1, ncol = 1, heights = unit(graph_heights, rep("mm", 9)), | |
240 top = textGrob(title_first_method[[args$first_plot_method]], gp = gpar(cex = 1), vjust = 0, just = "top"), | |
241 left = textGrob(legend_first_method[[args$first_plot_method]], gp = gpar(cex = 1), vjust = 0, hjust = 0, x = 1, y = (-0.41 / 7) * (end - start - (6.23 / 0.41)), rot = 90), | |
242 sub = textGrob(bottom_first_method[[args$first_plot_method]], gp = gpar(cex = 1), just = "bottom", vjust = 2) | |
235 ) | 243 ) |
236 ) | 244 ) |
237 do.call(grid.arrange, args_list) | 245 do.call(grid.arrange, args_list) |
238 } | 246 } |
239 devname=dev.off() | 247 devname <- dev.off() |
240 } | 248 } |
241 | 249 |
242 # main | 250 # main |
243 | 251 |
244 if (args$extra_plot_method != '') { double_plot() } | 252 if (args$extra_plot_method != "") { |
245 if (args$extra_plot_method == '' & !exists('global', where=args)) { | 253 double_plot() |
254 } | |
255 if (args$extra_plot_method == "" & !exists("global", where = args)) { | |
246 single_plot() | 256 single_plot() |
247 } | 257 } |
248 if (exists('global', where=args)) { | 258 if (exists("global", where = args)) { |
249 pdf(file=args$output, paper="special", height=11.69) | 259 pdf(file = args$output, paper = "special", height = 11.69) |
250 Table <- within(Table, Counts[Polarity=="R"] <- abs(Counts[Polarity=="R"])) # retropedalage | 260 table <- within(table, Counts[Polarity == "R"] <- abs(Counts[Polarity == "R"])) |
251 library(reshape2) | 261 library(reshape2) |
252 ml = melt(Table, id.vars = c("Dataset", "Chromosome", "Polarity", "Size")) | 262 ml <- melt(table, id.vars = c("Dataset", "Chromosome", "Polarity", "Size")) |
253 if (args$global == "nomerge") { | 263 if (args$global == "nomerge") { |
254 castml = dcast(ml, Dataset+Polarity+Size ~ variable, function(x) sum(x)) | 264 castml <- dcast(ml, Dataset + Polarity + Size ~ variable, function(x) sum(x)) |
255 castml <- within(castml, Counts[Polarity=="R"] <- (Counts[Polarity=="R"]*-1)) | 265 castml <- within(castml, Counts[Polarity == "R"] <- (Counts[Polarity == "R"] * -1)) |
256 bc = globalbc(castml, global="no") | 266 bc <- globalbc(castml, global = "no") |
257 } else { | 267 } else { |
258 castml = dcast(ml, Dataset+Size ~ variable, function(x) sum(x)) | 268 castml <- dcast(ml, Dataset + Size ~ variable, function(x) sum(x)) |
259 bc = globalbc(castml, global="yes") | 269 bc <- globalbc(castml, global = "yes") |
260 } | 270 } |
261 plot(bc) | 271 plot(bc) |
262 devname=dev.off() | 272 devname <- dev.off() |
263 } | 273 } |
264 |