... | ... |
@@ -1,17 +1,18 @@ |
1 | 1 |
## quiets concerns of R CMD check re: the .'s that appear in pipelines |
2 |
-if(getRversion() >= "2.15.1") utils::globalVariables(c("time", "Transition")) |
|
2 |
+if(getRversion() >= "2.15.1") utils::globalVariables(c()) |
|
3 |
+ |
|
3 | 4 |
|
4 | 5 |
#' Plot Extracted-ion chromatogram group. |
5 | 6 |
#' |
6 | 7 |
#' @importFrom tidyr gather |
7 |
-#' @importFrom ggplot2 ggplot ggtitle geom_vline geom_line theme theme_bw aes element_text |
|
8 |
+#' @importFrom ggplot2 ggplot ggtitle geom_vline geom_line theme theme_bw aes element_text xlab ylab |
|
8 | 9 |
#' @author Shubham Gupta, \email{shubh.gupta@mail.utoronto.ca} |
9 | 10 |
#' |
10 | 11 |
#' ORCID: 0000-0003-3500-8152 |
11 | 12 |
#' |
12 | 13 |
#' License: (c) Author (2019) + GPL-3 |
13 | 14 |
#' Date: 2019-12-13 |
14 |
-#' |
|
15 |
+#' @importFrom rlang .data |
|
15 | 16 |
#' @param XIC_group (list) It is a list of dataframe which has two columns. First column is for time |
16 | 17 |
#' and second column indicates intensity. |
17 | 18 |
#' @param peakAnnot (numeric) Peak-apex time. |
... | ... |
@@ -21,20 +22,21 @@ if(getRversion() >= "2.15.1") utils::globalVariables(c("time", "Transition")) |
21 | 22 |
#' dataPath <- system.file("extdata", package = "DIAlignR") |
22 | 23 |
#' runs <- c("hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt", |
23 | 24 |
#' "hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt") |
24 |
-#' XICs <- getXICs(analytes = "QFNNTDIVLLEDFQK_3", runs = runs, dataPath = dataPath, |
|
25 |
-#' XICfilter = "none") |
|
26 |
-#' plotXICgroup(XICs[["hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt"]][[1]]) |
|
25 |
+#' XICs <- getXICs(analytes = 4618L, runs = runs, dataPath = dataPath, oswMerged = TRUE) |
|
26 |
+#' plotXICgroup(XICs[["hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt"]][["4618"]]) |
|
27 |
+#' XICs <- smoothXICs(XICs[["hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt"]][["4618"]], |
|
28 |
+#' type = "sgolay", kernelLen = 13, polyOrd = 4) |
|
29 |
+#' plotXICgroup(XICs, Title = "Precursor 4618 \n |
|
30 |
+#' run hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt") |
|
27 | 31 |
#' |
28 |
-#' XICs <- getXICs(analytes = "14299_QFNNTDIVLLEDFQK/3", runs = runs, dataPath = dataPath, |
|
29 |
-#' XICfilter = "sgolay", SgolayFiltOrd = 4, SgolayFiltLen = 13, analyteInGroupLabel = TRUE) |
|
30 |
-#' plotXICgroup(XICs[["hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt"]][[1]]) |
|
31 | 32 |
#' @export |
32 | 33 |
plotXICgroup <- function(XIC_group, peakAnnot = NULL, Title =NULL){ |
33 | 34 |
df <- do.call("cbind", XIC_group) |
34 | 35 |
df <- df[,!duplicated(colnames(df))] |
35 | 36 |
colnames(df) <- c("time", paste("V", 1:(ncol(df)-1), sep="")) |
36 |
- df <- gather(df, key = "Transition", value = "Intensity", -time) |
|
37 |
- g <- ggplot(df, aes(time, Intensity, col=Transition)) + geom_line(show.legend = FALSE) + theme_bw() |
|
37 |
+ df <- gather(df, key = "Transition", value = "Intensity", -.data$time) |
|
38 |
+ g <- ggplot(df, aes(.data$time, .data$Intensity, col=.data$Transition)) + |
|
39 |
+ geom_line(show.legend = FALSE) + xlab("time") + ylab("intensity")+ theme_bw() |
|
38 | 40 |
if(!is.null(Title)) g <- g + ggtitle(paste0(Title)) + theme(plot.title = element_text(hjust = 0.5)) |
39 | 41 |
if(!is.null(peakAnnot)){ |
40 | 42 |
g <- g + geom_vline(xintercept=peakAnnot, lty="dotted", size = 0.4) |
... | ... |
@@ -42,6 +44,7 @@ plotXICgroup <- function(XIC_group, peakAnnot = NULL, Title =NULL){ |
42 | 44 |
return(g) |
43 | 45 |
} |
44 | 46 |
|
47 |
+ |
|
45 | 48 |
#' Plot extracted-ion chromatogram. |
46 | 49 |
#' |
47 | 50 |
#' |
... | ... |
@@ -52,17 +55,15 @@ plotXICgroup <- function(XIC_group, peakAnnot = NULL, Title =NULL){ |
52 | 55 |
#' License: (c) Author (2019) + GPL-3 |
53 | 56 |
#' Date: 2019-12-13 |
54 | 57 |
#' |
55 |
-#' @param analyte (string) An analyte is as PRECURSOR.GROUP_LABEL or as PEPTIDE.MODIFIED_SEQUENCE and PRECURSOR.CHARGE from osw file. |
|
58 |
+#' @param analyte (integer) an analyte is a PRECURSOR.ID from the osw file. |
|
56 | 59 |
#' @param run (string) Name of a mzml file without extension. |
57 |
-#' @param dataPath (char) Path to mzml and osw directory. |
|
60 |
+#' @param dataPath (string) path to mzml and osw directory. |
|
58 | 61 |
#' @param maxFdrQuery (numeric) A numeric value between 0 and 1. It is used to filter features from osw file which have SCORE_MS2.QVALUE less than itself. |
59 |
-#' @param XICfilter (string) This must be one of the strings "sgolay", "none". |
|
60 |
-#' @param SgolayFiltOrd (integer) It defines the polynomial order of filer. |
|
61 |
-#' @param SgolayFiltLen (integer) Must be an odd number. It defines the length of filter. |
|
62 |
+#' @param XICfilter (string) must be either sgolay, boxcar, gaussian, loess or none. |
|
63 |
+#' @param polyOrd (integer) order of the polynomial to be fit in the kernel. |
|
64 |
+#' @param kernelLen (integer) number of data-points to consider in the kernel. |
|
62 | 65 |
#' @param runType (char) This must be one of the strings "DIA_proteomics", "DIA_Metabolomics". |
63 | 66 |
#' @param oswMerged (logical) TRUE for experiment-wide FDR and FALSE for run-specific FDR by pyprophet. |
64 |
-#' @param nameCutPattern (string) regex expression to fetch mzML file name from RUN.FILENAME columns of osw files. |
|
65 |
-#' @param analyteInGroupLabel (logical) TRUE for getting analytes as PRECURSOR.GROUP_LABEL from osw file. |
|
66 | 67 |
#' @param peakAnnot (numeric) Peak-apex time. |
67 | 68 |
#' @param Title (logical) TRUE: name of the list will be displayed as title. |
68 | 69 |
#' |
... | ... |
@@ -71,23 +72,23 @@ plotXICgroup <- function(XIC_group, peakAnnot = NULL, Title =NULL){ |
71 | 72 |
#' @examples |
72 | 73 |
#' dataPath <- system.file("extdata", package = "DIAlignR") |
73 | 74 |
#' run <- "hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt" |
74 |
-#' plotAnalyteXICs(analyte = "QFNNTDIVLLEDFQK_3", run, dataPath = dataPath, XICfilter = "none") |
|
75 |
-#' plotAnalyteXICs(analyte = "14299_QFNNTDIVLLEDFQK/3", run, dataPath = dataPath, |
|
76 |
-#' XICfilter = "sgolay", analyteInGroupLabel = TRUE) |
|
75 |
+#' plotAnalyteXICs(analyte = 2474L, run, dataPath = dataPath, oswMerged = TRUE, XICfilter = "none") |
|
76 |
+#' plotAnalyteXICs(analyte = 2474L, run, dataPath = dataPath, oswMerged = TRUE, XICfilter = "sgolay") |
|
77 | 77 |
#' @export |
78 | 78 |
plotAnalyteXICs <- function(analyte, run, dataPath = ".", maxFdrQuery = 1.0, |
79 |
- XICfilter = "sgolay", SgolayFiltOrd = 4, SgolayFiltLen = 9, |
|
80 |
- runType = "DIA_proteomics", oswMerged = TRUE, nameCutPattern = "(.*)(/)(.*)", |
|
81 |
- analyteInGroupLabel = FALSE, peakAnnot = NULL, Title = NULL){ |
|
79 |
+ XICfilter = "sgolay", polyOrd = 4, kernelLen = 9, |
|
80 |
+ runType = "DIA_proteomics", oswMerged = TRUE, |
|
81 |
+ peakAnnot = NULL, Title = NULL){ |
|
82 | 82 |
if((length(run) != 1) | (length(analyte) != 1)){ |
83 | 83 |
return(stop("One analyte and single run are needed.")) |
84 | 84 |
} |
85 | 85 |
XICs <- getXICs(analytes = analyte, runs = run, dataPath = dataPath, maxFdrQuery = maxFdrQuery, |
86 |
- XICfilter = XICfilter, SgolayFiltOrd = SgolayFiltOrd, SgolayFiltLen = SgolayFiltLen, |
|
87 |
- runType = runType, oswMerged = oswMerged, nameCutPattern = nameCutPattern, analyteInGroupLabel = analyteInGroupLabel) |
|
88 |
- plotXICgroup(XICs[[run]][[analyte]], peakAnnot, Title) |
|
86 |
+ runType = runType, oswMerged = oswMerged) |
|
87 |
+ XICs <- smoothXICs(XICs[[run]][[1]], type=XICfilter, kernelLen = kernelLen, polyOrd = polyOrd) |
|
88 |
+ plotXICgroup(XICs, peakAnnot, Title) |
|
89 | 89 |
} |
90 | 90 |
|
91 |
+ |
|
91 | 92 |
#' Plot an aligned XIC-group. |
92 | 93 |
#' |
93 | 94 |
#' @details |
... | ... |
@@ -111,22 +112,27 @@ plotSingleAlignedChrom <- function(XIC_group, idx, peakAnnot = NULL){ |
111 | 112 |
# Update intensities with aligned time indices. |
112 | 113 |
for(k in seq_along(XIC_group)){ |
113 | 114 |
mutateInt <- XIC_group[[k]][idx, 2] |
114 |
- mutateInt <- na.locf(na.locf(mutateInt, na.rm = FALSE),fromLast = TRUE) |
|
115 |
+ mutateInt <- na.locf(na.locf(na.approx(mutateInt, na.rm = FALSE), na.rm = FALSE), fromLast = TRUE) |
|
115 | 116 |
intensity[[k]] <- mutateInt |
116 | 117 |
} |
117 |
- #TODO: interpolate mutateT so that it can be plotted on x-axis. |
|
118 | 118 |
mutateT <- mapIdxToTime(XIC_group[[1]][, "time"], idx) |
119 |
+ df <- data.frame(x = which(!is.na(mutateT)), y = mutateT[!is.na(mutateT)] ) |
|
120 |
+ fit <- lm(y ~ x, df) |
|
121 |
+ df <- data.frame(x = which(is.na(mutateT)), y = NA) |
|
122 |
+ df$y <- predict(fit, newdata = df) |
|
123 |
+ for(i in nrow(df)) mutateT[df$x[i]] <- df$y[i] |
|
124 |
+ |
|
119 | 125 |
df <- do.call("cbind", intensity) |
120 |
- Index <- 1:nrow(df) |
|
121 |
- df <- cbind(Index, as.data.frame(df)) |
|
122 |
- df <- gather(df, key = "Transition", value = "Intensity", -Index) |
|
126 |
+ df <- cbind(mutateT, as.data.frame(df)) |
|
127 |
+ df <- gather(df, key = "Transition", value = "Intensity", -mutateT) |
|
123 | 128 |
# Plot chromatogram |
124 |
- g <- ggplot(df, aes(Index, Intensity, col=Transition)) + geom_line(show.legend = FALSE) + theme_bw() |
|
129 |
+ g <- ggplot(df, aes(mutateT, .data$Intensity, col=.data$Transition)) + geom_line(show.legend = FALSE) + theme_bw() |
|
125 | 130 |
if(!is.null(peakAnnot)){ |
126 | 131 |
g <- g + geom_vline(xintercept=peakAnnot, lty="dotted", size = 0.4) |
127 | 132 |
} |
128 | 133 |
return(g)} |
129 | 134 |
|
135 |
+ |
|
130 | 136 |
#' Plot aligned XICs group for a specific peptide. |
131 | 137 |
#' |
132 | 138 |
#' @description |
... | ... |
@@ -150,21 +156,25 @@ plotSingleAlignedChrom <- function(XIC_group, idx, peakAnnot = NULL){ |
150 | 156 |
#' @param annotatePeak (logical) TRUE: Peak boundaries and apex will be highlighted. |
151 | 157 |
#' @return A plot to the current device. |
152 | 158 |
#' |
159 |
+#' @keywords internal |
|
153 | 160 |
#' @examples |
154 | 161 |
#' dataPath <- system.file("extdata", package = "DIAlignR") |
155 | 162 |
#' runs <- c("hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt", |
156 | 163 |
#' "hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt") |
157 |
-#' AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath) |
|
158 |
-#' AlignObj <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[1]] |
|
159 |
-#' XICs.ref <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[2]] |
|
160 |
-#' XICs.eXp <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[3]] |
|
161 |
-#' refPeakLabel <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[4]] |
|
162 |
-#' @keywords internal |
|
164 |
+#' AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath) |
|
165 |
+#' AlignObj <- AlignObjOutput[[2]][["4618"]][[1]][["AlignObj"]] |
|
166 |
+#' XICs.ref <- AlignObjOutput[[2]][["4618"]][[1]][["ref"]] |
|
167 |
+#' XICs.eXp <- AlignObjOutput[[2]][["4618"]][[1]][["eXp"]] |
|
168 |
+#' refPeakLabel <- AlignObjOutput[[2]][["4618"]][[1]][["peak"]] |
|
169 |
+#' \dontrun{ |
|
170 |
+#' getAlignedFigs(AlignObj, XICs.ref, XICs.eXp, refPeakLabel) |
|
171 |
+#' } |
|
163 | 172 |
getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
164 | 173 |
annotatePeak = FALSE){ |
165 |
- AlignedIndices <- cbind(AlignObj@indexA_aligned, AlignObj@indexB_aligned, |
|
166 |
- AlignObj@score) |
|
167 |
- colnames(AlignedIndices) <- c("indexAligned.ref", "indexAligned.eXp", "score") |
|
174 |
+ AlignedIndices <- cbind(slot(AlignObj, "indexA_aligned"), |
|
175 |
+ slot(AlignObj, "indexB_aligned")) |
|
176 |
+ colnames(AlignedIndices) <- c("indexAligned.ref", "indexAligned.eXp") |
|
177 |
+ # Do not include gaps in reference run. |
|
168 | 178 |
AlignedIndices <- AlignedIndices[(AlignedIndices[,"indexAligned.ref"] != 0L), ] |
169 | 179 |
AlignedIndices[, 1:2][AlignedIndices[, 1:2] == 0] <- NA |
170 | 180 |
t.ref <- XICs.ref[[1]][["time"]] |
... | ... |
@@ -178,7 +188,7 @@ getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
178 | 188 |
geom_vline(xintercept=refPeakLabel$rightWidth[1], lty="dashed", size = 0.1) |
179 | 189 |
} |
180 | 190 |
|
181 |
- peXpU <- plotXICgroup(XICs.eXp) + scale_y_continuous(labels = scientific_format(digits = 1)) + xlab("eXp time") |
|
191 |
+ peXpU <- plotXICgroup(XICs.eXp) + scale_y_continuous(labels = scientific_format(digits = 1)) + xlab("eXp unaligned time") |
|
182 | 192 |
if(annotatePeak){ |
183 | 193 |
peXpU <- peXpU + |
184 | 194 |
geom_vline(xintercept=t.eXp[which.min(abs(t.ref - refPeakLabel$RT[1]))], lty="dotted", size = 0.3) + |
... | ... |
@@ -188,7 +198,7 @@ getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
188 | 198 |
|
189 | 199 |
###################### Plot aligned chromatogram ###################################### |
190 | 200 |
peXpA <- plotSingleAlignedChrom(XICs.eXp, idx = AlignedIndices[,"indexAligned.eXp"]) + |
191 |
- scale_y_continuous(labels = scientific_format(digits = 1)) + xlab("eXp Aligned index") |
|
201 |
+ scale_y_continuous(labels = scientific_format(digits = 1)) + xlab("eXp aligned index") |
|
192 | 202 |
if(annotatePeak){ |
193 | 203 |
peXpA <- peXpA + |
194 | 204 |
geom_vline(xintercept=which.min(abs(t.ref - refPeakLabel$RT[1])), |
... | ... |
@@ -204,6 +214,7 @@ getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
204 | 214 |
figs |
205 | 215 |
} |
206 | 216 |
|
217 |
+ |
|
207 | 218 |
#' Plot aligned XICs group for a specific peptide. |
208 | 219 |
#' AlignObjOutput is the output from getAlignObjs fucntion. |
209 | 220 |
#' |
... | ... |
@@ -215,9 +226,9 @@ getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
215 | 226 |
#' License: (c) Author (2019) + GPL-3 |
216 | 227 |
#' Date: 2019-12-13 |
217 | 228 |
#' |
218 |
-#' @param AlignObjOutput (list) The list contains AlignObj, raw XICs for reference and experiment, and reference-peak label. |
|
219 |
-#' @param plotType This must be one of the strings "All", "onlyUnaligned" and "onlyAligned". |
|
220 |
-#' @param DrawAlignR (logical) TRUE: ggplot objects will be returned. |
|
229 |
+#' @param AlignObjOutput (list) list contains fileInfo, AlignObj, raw XICs for reference and experiment, and reference-peak label. |
|
230 |
+#' @param plotType (string) must be one of the strings "All", "onlyUnaligned" and "onlyAligned". |
|
231 |
+#' @param outFile (string) name of the output pdf file. |
|
221 | 232 |
#' @param annotatePeak (logical) TRUE: Peak boundaries and apex will be highlighted. |
222 | 233 |
#' @param saveFigs (logical) TRUE: Figures will be saved in AlignedAnalytes.pdf . |
223 | 234 |
#' @return A plot to the current device. |
... | ... |
@@ -226,42 +237,46 @@ getAlignedFigs <- function(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, |
226 | 237 |
#' dataPath <- system.file("extdata", package = "DIAlignR") |
227 | 238 |
#' runs <- c("hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt", |
228 | 239 |
#' "hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt") |
229 |
-#' AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath) |
|
240 |
+#' AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath) |
|
230 | 241 |
#' plotAlignedAnalytes(AlignObjOutput) |
231 | 242 |
#' @export |
232 |
-plotAlignedAnalytes <- function(AlignObjOutput, plotType = "All", DrawAlignR = FALSE, |
|
243 |
+plotAlignedAnalytes <- function(AlignObjOutput, plotType = "All", outFile = "AlignedAnalytes.pdf", |
|
233 | 244 |
annotatePeak = FALSE, saveFigs = FALSE){ |
234 |
- if((length(AlignObjOutput) > 1) | saveFigs){ |
|
235 |
- grDevices::pdf("AlignedAnalytes.pdf") |
|
245 |
+ if((length(AlignObjOutput[[2]][[1]]) > 1) | length(AlignObjOutput[[2]]) > 1 | saveFigs){ |
|
246 |
+ grDevices::pdf(outFile) |
|
236 | 247 |
} |
237 |
- for(i in seq_along(AlignObjOutput)){ |
|
238 |
- if(is.null(AlignObjOutput[[i]])){ |
|
248 |
+ # Get fileInfo (output of getRunNames) |
|
249 |
+ vec <- AlignObjOutput[[1]][,"runName"] |
|
250 |
+ names(vec) <- rownames(AlignObjOutput[[1]]) |
|
251 |
+ # Iterate over each precursor, check if it is NULL. |
|
252 |
+ for(i in seq_along(AlignObjOutput[[2]])){ |
|
253 |
+ if(is.null(AlignObjOutput[[2]][[i]])){ |
|
239 | 254 |
next |
240 | 255 |
} |
241 |
- AlignObj <- AlignObjOutput[[i]][[1]] |
|
242 |
- XICs.ref <- AlignObjOutput[[i]][[2]] |
|
243 |
- XICs.eXp <- AlignObjOutput[[i]][[3]] |
|
244 |
- refPeakLabel <- AlignObjOutput[[i]][[4]] |
|
245 |
- analyte <- names(AlignObjOutput)[i] |
|
246 |
- refRun <- names(AlignObjOutput[[i]])[2] |
|
247 |
- eXpRun <- names(AlignObjOutput[[i]])[3] |
|
248 |
- figs <- getAlignedFigs(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, annotatePeak) |
|
249 |
- |
|
250 |
- if(DrawAlignR){ |
|
251 |
- return(figs)} |
|
256 |
+ pairs <- names(AlignObjOutput[[2]][[i]]) |
|
257 |
+ for(pair in pairs){ |
|
258 |
+ refRun <- strsplit(pair, split = "_")[[1]][1] |
|
259 |
+ eXpRun <- strsplit(pair, split = "_")[[1]][2] |
|
260 |
+ AlignObj <- AlignObjOutput[[2]][[i]][[pair]][["AlignObj"]] |
|
261 |
+ XICs.ref <- AlignObjOutput[[2]][[i]][[pair]][["ref"]] |
|
262 |
+ XICs.eXp <- AlignObjOutput[[2]][[i]][[pair]][["eXp"]] |
|
263 |
+ refPeakLabel <- AlignObjOutput[[2]][[i]][[pair]][["peak" ]] |
|
252 | 264 |
|
253 |
- if(plotType == "onlyAligned"){ |
|
254 |
- grid.arrange(figs[["prefU"]], figs[["peXpA"]], nrow=2, ncol=1, |
|
255 |
- top = paste0(analyte,"\n", "ref: ", refRun, "\n", "eXp: ", eXpRun )) |
|
256 |
- } else if(plotType == "onlyUnaligned"){ |
|
257 |
- grid.arrange(figs[["prefU"]], figs[["peXpU"]], nrow=2, ncol=1, |
|
258 |
- top = paste0(analyte,"\n", "ref: ", refRun, "\n", "eXp: ", eXpRun )) |
|
259 |
- } else{ |
|
260 |
- grid.arrange(figs[["peXpU"]], figs[["prefU"]], figs[["peXpA"]], |
|
261 |
- nrow=3, ncol=1, top = paste0(analyte,"\n", "ref: ", refRun, "\n", "eXp: ", eXpRun )) |
|
265 |
+ analyte <- names(AlignObjOutput[[2]])[i] |
|
266 |
+ figs <- getAlignedFigs(AlignObj, XICs.ref, XICs.eXp, refPeakLabel, annotatePeak) |
|
267 |
+ if(plotType == "onlyAligned"){ |
|
268 |
+ grid.arrange(figs[["prefU"]], figs[["peXpA"]], nrow=2, ncol=1, |
|
269 |
+ top = paste0(analyte,"\n", "ref: ", refRun, "\n", "eXp: ", eXpRun )) |
|
270 |
+ } else if(plotType == "onlyUnaligned"){ |
|
271 |
+ grid.arrange(figs[["prefU"]], figs[["peXpU"]], nrow=2, ncol=1, |
|
272 |
+ top = paste0(analyte,"\n", "ref: ", refRun, "\n", "eXp: ", eXpRun )) |
|
273 |
+ } else{ |
|
274 |
+ grid.arrange(figs[["prefU"]], figs[["peXpA"]], figs[["peXpU"]], |
|
275 |
+ nrow=3, ncol=1, top = paste0(analyte,"\n", "ref: ", vec[[refRun]], "\n", "eXp: ", vec[[eXpRun]] )) |
|
276 |
+ } |
|
262 | 277 |
} |
263 | 278 |
} |
264 |
- if((length(AlignObjOutput) > 1) | saveFigs){ |
|
279 |
+ if((length(AlignObjOutput[[2]][[1]]) > 1) | length(AlignObjOutput[[2]]) > 1 | saveFigs){ |
|
265 | 280 |
grDevices::dev.off() |
266 | 281 |
} |
267 | 282 |
} |
... | ... |
@@ -286,16 +301,22 @@ plotAlignedAnalytes <- function(AlignObjOutput, plotType = "All", DrawAlignR = F |
286 | 301 |
#' dataPath <- system.file("extdata", package = "DIAlignR") |
287 | 302 |
#' runs <- c("hroest_K120809_Strep0%PlasmaBiolRepl2_R04_SW_filt", |
288 | 303 |
#' "hroest_K120809_Strep10%PlasmaBiolRepl2_R04_SW_filt") |
289 |
-#' AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath, |
|
290 |
-#' objType = "medium") |
|
304 |
+#' AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath, objType = "medium") |
|
291 | 305 |
#' plotAlignmentPath(AlignObjOutput) |
292 | 306 |
#' @export |
293 | 307 |
plotAlignmentPath <- function(AlignObjOutput){ |
294 |
- Alignobj <- AlignObjOutput[[1]][[1]] |
|
295 |
- analyte <- names(AlignObjOutput)[1] |
|
296 |
- s <- Alignobj@s |
|
297 |
- Path <- Alignobj@path[2:nrow(Alignobj@path), 2:ncol(Alignobj@path)] |
|
298 |
- lattice::levelplot(s, axes = TRUE, xlab = "ref index", ylab = "eXp index", |
|
308 |
+ vec <- AlignObjOutput[[1]][,"runName"] |
|
309 |
+ names(vec) <- rownames(AlignObjOutput[[1]]) |
|
310 |
+ pair <- names(AlignObjOutput[[2]][[1]]) |
|
311 |
+ ref <- strsplit(pair, split = "_")[[1]][1] |
|
312 |
+ eXp <- strsplit(pair, split = "_")[[1]][2] |
|
313 |
+ AlignObj <- AlignObjOutput[[2]][[1]][[pair]][["AlignObj"]] |
|
314 |
+ analyte <- names(AlignObjOutput[[2]])[1] |
|
315 |
+ |
|
316 |
+ s <- slot(AlignObj, "s") |
|
317 |
+ Path <- slot(AlignObj, "path") |
|
318 |
+ Path <- Path[2:nrow(Path), 2:ncol(Path)] |
|
319 |
+ lattice::levelplot(s, axes = TRUE, xlab = vec[[ref]], ylab = vec[[eXp]], |
|
299 | 320 |
main = paste0("Hybrid alignment through the similarity matrix\n for ", |
300 | 321 |
analyte), fontsize = 7) + |
301 | 322 |
latticeExtra::as.layer(lattice::levelplot(Path, col.regions = c("transparent", "green"), |
... | ... |
@@ -30,11 +30,14 @@ AlignObj is the output from getAlignObjs fucntion. This function prepares ggplot |
30 | 30 |
dataPath <- system.file("extdata", package = "DIAlignR") |
31 | 31 |
runs <- c("hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt", |
32 | 32 |
"hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt") |
33 |
-AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath) |
|
34 |
-AlignObj <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[1]] |
|
35 |
-XICs.ref <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[2]] |
|
36 |
-XICs.eXp <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[3]] |
|
37 |
-refPeakLabel <- AlignObjOutput[["QFNNTDIVLLEDFQK_3"]][[4]] |
|
33 |
+AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath) |
|
34 |
+AlignObj <- AlignObjOutput[[2]][["4618"]][[1]][["AlignObj"]] |
|
35 |
+XICs.ref <- AlignObjOutput[[2]][["4618"]][[1]][["ref"]] |
|
36 |
+XICs.eXp <- AlignObjOutput[[2]][["4618"]][[1]][["eXp"]] |
|
37 |
+refPeakLabel <- AlignObjOutput[[2]][["4618"]][[1]][["peak"]] |
|
38 |
+\dontrun{ |
|
39 |
+getAlignedFigs(AlignObj, XICs.ref, XICs.eXp, refPeakLabel) |
|
40 |
+} |
|
38 | 41 |
} |
39 | 42 |
\author{ |
40 | 43 |
Shubham Gupta, \email{shubh.gupta@mail.utoronto.ca} |
... | ... |
@@ -6,14 +6,15 @@ |
6 | 6 |
AlignObjOutput is the output from getAlignObjs fucntion.} |
7 | 7 |
\usage{ |
8 | 8 |
plotAlignedAnalytes(AlignObjOutput, plotType = "All", |
9 |
- DrawAlignR = FALSE, annotatePeak = FALSE, saveFigs = FALSE) |
|
9 |
+ outFile = "AlignedAnalytes.pdf", annotatePeak = FALSE, |
|
10 |
+ saveFigs = FALSE) |
|
10 | 11 |
} |
11 | 12 |
\arguments{ |
12 |
-\item{AlignObjOutput}{(list) The list contains AlignObj, raw XICs for reference and experiment, and reference-peak label.} |
|
13 |
+\item{AlignObjOutput}{(list) list contains fileInfo, AlignObj, raw XICs for reference and experiment, and reference-peak label.} |
|
13 | 14 |
|
14 |
-\item{plotType}{This must be one of the strings "All", "onlyUnaligned" and "onlyAligned".} |
|
15 |
+\item{plotType}{(string) must be one of the strings "All", "onlyUnaligned" and "onlyAligned".} |
|
15 | 16 |
|
16 |
-\item{DrawAlignR}{(logical) TRUE: ggplot objects will be returned.} |
|
17 |
+\item{outFile}{(string) name of the output pdf file.} |
|
17 | 18 |
|
18 | 19 |
\item{annotatePeak}{(logical) TRUE: Peak boundaries and apex will be highlighted.} |
19 | 20 |
|
... | ... |
@@ -30,7 +31,7 @@ AlignObjOutput is the output from getAlignObjs fucntion. |
30 | 31 |
dataPath <- system.file("extdata", package = "DIAlignR") |
31 | 32 |
runs <- c("hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt", |
32 | 33 |
"hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt") |
33 |
-AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath) |
|
34 |
+AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath) |
|
34 | 35 |
plotAlignedAnalytes(AlignObjOutput) |
35 | 36 |
} |
36 | 37 |
\author{ |
... | ... |
@@ -21,8 +21,7 @@ library(lattice) |
21 | 21 |
dataPath <- system.file("extdata", package = "DIAlignR") |
22 | 22 |
runs <- c("hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt", |
23 | 23 |
"hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt") |
24 |
-AlignObjOutput <- getAlignObjs(analytes = "QFNNTDIVLLEDFQK_3", runs, dataPath = dataPath, |
|
25 |
- objType = "medium") |
|
24 |
+AlignObjOutput <- getAlignObjs(analytes = 4618L, runs, dataPath = dataPath, objType = "medium") |
|
26 | 25 |
plotAlignmentPath(AlignObjOutput) |
27 | 26 |
} |
28 | 27 |
\author{ |
... | ... |
@@ -5,34 +5,29 @@ |
5 | 5 |
\title{Plot extracted-ion chromatogram.} |
6 | 6 |
\usage{ |
7 | 7 |
plotAnalyteXICs(analyte, run, dataPath = ".", maxFdrQuery = 1, |
8 |
- XICfilter = "sgolay", SgolayFiltOrd = 4, SgolayFiltLen = 9, |
|
9 |
- runType = "DIA_proteomics", oswMerged = TRUE, |
|
10 |
- nameCutPattern = "(.*)(/)(.*)", analyteInGroupLabel = FALSE, |
|
11 |
- peakAnnot = NULL, Title = NULL) |
|
8 |
+ XICfilter = "sgolay", polyOrd = 4, kernelLen = 9, |
|
9 |
+ runType = "DIA_proteomics", oswMerged = TRUE, peakAnnot = NULL, |
|
10 |
+ Title = NULL) |
|
12 | 11 |
} |
13 | 12 |
\arguments{ |
14 |
-\item{analyte}{(string) An analyte is as PRECURSOR.GROUP_LABEL or as PEPTIDE.MODIFIED_SEQUENCE and PRECURSOR.CHARGE from osw file.} |
|
13 |
+\item{analyte}{(integer) an analyte is a PRECURSOR.ID from the osw file.} |
|
15 | 14 |
|
16 | 15 |
\item{run}{(string) Name of a mzml file without extension.} |
17 | 16 |
|
18 |
-\item{dataPath}{(char) Path to mzml and osw directory.} |
|
17 |
+\item{dataPath}{(string) path to mzml and osw directory.} |
|
19 | 18 |
|
20 | 19 |
\item{maxFdrQuery}{(numeric) A numeric value between 0 and 1. It is used to filter features from osw file which have SCORE_MS2.QVALUE less than itself.} |
21 | 20 |
|
22 |
-\item{XICfilter}{(string) This must be one of the strings "sgolay", "none".} |
|
21 |
+\item{XICfilter}{(string) must be either sgolay, boxcar, gaussian, loess or none.} |
|
23 | 22 |
|
24 |
-\item{SgolayFiltOrd}{(integer) It defines the polynomial order of filer.} |
|
23 |
+\item{polyOrd}{(integer) order of the polynomial to be fit in the kernel.} |
|
25 | 24 |
|
26 |
-\item{SgolayFiltLen}{(integer) Must be an odd number. It defines the length of filter.} |
|
25 |
+\item{kernelLen}{(integer) number of data-points to consider in the kernel.} |
|
27 | 26 |
|
28 | 27 |
\item{runType}{(char) This must be one of the strings "DIA_proteomics", "DIA_Metabolomics".} |
29 | 28 |
|
30 | 29 |
\item{oswMerged}{(logical) TRUE for experiment-wide FDR and FALSE for run-specific FDR by pyprophet.} |
31 | 30 |
|
32 |
-\item{nameCutPattern}{(string) regex expression to fetch mzML file name from RUN.FILENAME columns of osw files.} |
|
33 |
- |
|
34 |
-\item{analyteInGroupLabel}{(logical) TRUE for getting analytes as PRECURSOR.GROUP_LABEL from osw file.} |
|
35 |
- |
|
36 | 31 |
\item{peakAnnot}{(numeric) Peak-apex time.} |
37 | 32 |
|
38 | 33 |
\item{Title}{(logical) TRUE: name of the list will be displayed as title.} |
... | ... |
@@ -46,9 +41,8 @@ Plot extracted-ion chromatogram. |
46 | 41 |
\examples{ |
47 | 42 |
dataPath <- system.file("extdata", package = "DIAlignR") |
48 | 43 |
run <- "hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt" |
49 |
-plotAnalyteXICs(analyte = "QFNNTDIVLLEDFQK_3", run, dataPath = dataPath, XICfilter = "none") |
|
50 |
-plotAnalyteXICs(analyte = "14299_QFNNTDIVLLEDFQK/3", run, dataPath = dataPath, |
|
51 |
-XICfilter = "sgolay", analyteInGroupLabel = TRUE) |
|
44 |
+plotAnalyteXICs(analyte = 2474L, run, dataPath = dataPath, oswMerged = TRUE, XICfilter = "none") |
|
45 |
+plotAnalyteXICs(analyte = 2474L, run, dataPath = dataPath, oswMerged = TRUE, XICfilter = "sgolay") |
|
52 | 46 |
} |
53 | 47 |
\author{ |
54 | 48 |
Shubham Gupta, \email{shubh.gupta@mail.utoronto.ca} |
... | ... |
@@ -24,13 +24,13 @@ Plot Extracted-ion chromatogram group. |
24 | 24 |
dataPath <- system.file("extdata", package = "DIAlignR") |
25 | 25 |
runs <- c("hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt", |
26 | 26 |
"hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt") |
27 |
-XICs <- getXICs(analytes = "QFNNTDIVLLEDFQK_3", runs = runs, dataPath = dataPath, |
|
28 |
- XICfilter = "none") |
|
29 |
-plotXICgroup(XICs[["hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt"]][[1]]) |
|
27 |
+XICs <- getXICs(analytes = 4618L, runs = runs, dataPath = dataPath, oswMerged = TRUE) |
|
28 |
+plotXICgroup(XICs[["hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt"]][["4618"]]) |
|
29 |
+XICs <- smoothXICs(XICs[["hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt"]][["4618"]], |
|
30 |
+ type = "sgolay", kernelLen = 13, polyOrd = 4) |
|
31 |
+plotXICgroup(XICs, Title = "Precursor 4618 \\n |
|
32 |
+ run hroest_K120809_Strep0\%PlasmaBiolRepl2_R04_SW_filt") |
|
30 | 33 |
|
31 |
-XICs <- getXICs(analytes = "14299_QFNNTDIVLLEDFQK/3", runs = runs, dataPath = dataPath, |
|
32 |
- XICfilter = "sgolay", SgolayFiltOrd = 4, SgolayFiltLen = 13, analyteInGroupLabel = TRUE) |
|
33 |
-plotXICgroup(XICs[["hroest_K120809_Strep10\%PlasmaBiolRepl2_R04_SW_filt"]][[1]]) |
|
34 | 34 |
} |
35 | 35 |
\author{ |
36 | 36 |
Shubham Gupta, \email{shubh.gupta@mail.utoronto.ca} |