Skip to content

Commit 9f78385

Browse files
authored
Merge pull request #81 from NorStorz/feature/qfeature
Feature/qfeature
2 parents 06638e5 + c8142d2 commit 9f78385

9 files changed

+54
-23
lines changed

.Rbuildignore

+2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
^.*\.Rproj$
2+
^\.Rproj\.user$

IntMedDf.Rdata

308 KB
Binary file not shown.

MetFamily.Rproj

+17
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
Version: 1.0
2+
3+
RestoreWorkspace: Default
4+
SaveWorkspace: Default
5+
AlwaysSaveHistory: Default
6+
7+
EnableCodeIndexing: Yes
8+
UseSpacesForTab: Yes
9+
NumSpacesForTab: 2
10+
Encoding: UTF-8
11+
12+
RnwWeave: Sweave
13+
LaTeX: pdfLaTeX
14+
15+
BuildType: Package
16+
PackageUseDevtools: Yes
17+
PackageInstallArgs: --no-multiarch --with-keep.source

R/FragmentMatrixFunctions.R

+4
Original file line numberDiff line numberDiff line change
@@ -1585,6 +1585,10 @@ convertToProjectFile2 <- function(filePeakMatrixQF,
15851585
metaboliteFamilies <- metaboliteFamilies[orderMS1features]
15861586
furtherProperties <- lapply(X = furtherProperties, FUN = function(props){props[orderMS1features]})
15871587

1588+
#TODO: resolve ?
1589+
#temporary fix
1590+
#filePeakMatrix <- NULL
1591+
15881592
if(!is.null(filePeakMatrix)){
15891593
## allHits: dataFrame$"Average Mz" --> precursorMz; allHits indexes the spectraList
15901594
diffAll <- abs(outer(X = precursorMz, Y = dataFrame$"Average Mz", FUN = function(x, y){abs(x-y)}))

R/parsePeakAbundanceMatrixQF.R

+23-17
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@
1111
#' @export
1212
#'
1313
#' @examples
14+
1415
parsePeakAbundanceMatrixQF <- function(qfeatures,
1516
doPrecursorDeisotoping,
1617
mzDeviationInPPM_precursorDeisotoping,
@@ -19,33 +20,36 @@ parsePeakAbundanceMatrixQF <- function(qfeatures,
1920
progress=FALSE)
2021
{
2122
## read file
22-
2323
if(!is.na(progress)) {
2424
if(progress) {
2525
incProgress(amount = 0.1, detail = paste("Parsing MS1 file content...", sep = ""))
2626
} else {
2727
print(paste("Parsing MS1 file content...", sep = ""))
2828
}
2929
}
30+
31+
32+
3033

3134
cols_to_exclude <- c("Reference RT","Reference m/z","Comment",
3235
"Manually modified for quantification",
3336
"Total score","RT similarity","Average","Stdev")
3437

3538
cols_to_keep <- which(!colnames(rowData(qfeatures))[[1]] %in% cols_to_exclude)
36-
39+
3740
dataFrame <- cbind(rowData(qfeatures)[[1]][,cols_to_keep] ,assay(qfeatures))
38-
39-
ncol(rowData(qfeatures)[[1]])
41+
#workaround for avoiding change in colnames during coercion
42+
cnames <- colnames(dataFrame)
43+
dataFrame <- as.data.frame(dataFrame)
44+
colnames(dataFrame) <- cnames
45+
oldFormat <- ncol(colData(qfeatures))==3
46+
numRowDataCols <- ncol(rowData(qfeatures)[[1]])
47+
dataColumnStartEndIndeces <- c(numRowDataCols+1,ncol(dataFrame))
4048
numberOfPrecursors <- nrow(dataFrame)
4149
numberOfPrecursorsPrior <- numberOfPrecursors
42-
4350

44-
45-
if(nrow(colData(qfeatures))>0){
46-
47-
dataColumnStartEndIndeces <- 1
48-
numberOfDataColumns <- nrow(colData(qfeatures))
51+
if(ncol(assay(qfeatures))>0){
52+
numberOfDataColumns <- ncol(assay(qfeatures))
4953
sampleClass <- colData(qfeatures)$Class
5054
sampleType <- colData(qfeatures)$Type
5155
sampleInjectionOrder <- colData(qfeatures)$"Injection order"
@@ -74,7 +78,7 @@ parsePeakAbundanceMatrixQF <- function(qfeatures,
7478

7579
## replace -1 by 0
7680
if(numberOfDataColumns > 0) {
77-
for(colIdx in dataColumnStartEndIndeces[[1]]:dataColumnStartEndIndeces[[2]]){
81+
for(colIdx in (numRowDataCols+1):ncol(dataFrame)){
7882
dataFrame[ , colIdx] <- gsub(x = gsub(x = dataFrame[ , colIdx], pattern = "\\.", replacement = ""), pattern = ",", replacement = ".")
7983
}
8084
}
@@ -97,13 +101,13 @@ parsePeakAbundanceMatrixQF <- function(qfeatures,
97101

98102
## replace -1 by 0
99103
if(numberOfDataColumns > 0){
100-
for(colIdx in dataColumnStartEndIndeces[[1]]:dataColumnStartEndIndeces[[2]]){
104+
for(colIdx in (numRowDataCols+1):ncol(dataFrame)){
101105
dataFrame[ , colIdx] <- as.numeric(dataFrame[ , colIdx])
102106
if(!is.na(sum(dataFrame[,colIdx] == -1)))
103107
dataFrame[(dataFrame[,colIdx] == -1),colIdx] <- 0
104108
}
105109
}
106-
110+
vals <- NULL
107111
## deisotoping
108112
numberOfRemovedIsotopePeaks <- 0
109113
if(doPrecursorDeisotoping & !is.null(dataFrame$"Average Mz")){
@@ -114,7 +118,7 @@ parsePeakAbundanceMatrixQF <- function(qfeatures,
114118
precursorsToRemove <- vector(mode = "logical", length = numberOfPrecursors)
115119

116120
if(numberOfDataColumns > 0){
117-
intensities <- dataFrame[ , dataColumnStartEndIndeces[[1]]:dataColumnStartEndIndeces[[2]]]
121+
intensities <- dataFrame[ , (numRowDataCols+1):ncol(dataFrame)]
118122
medians <- apply(X = as.matrix(intensities), MARGIN = 1, FUN = median)
119123
}
120124

@@ -139,21 +143,23 @@ parsePeakAbundanceMatrixQF <- function(qfeatures,
139143
} else {
140144
validPrecursorsInIntensity <- TRUE
141145
}
142-
146+
143147
if(any(validPrecursorsInRt & validPrecursorsInMz & validPrecursorsInIntensity))
144148
precursorsToRemove[[precursorIdx]] <- TRUE
145-
}
146149

150+
}
151+
147152
## remove isotopes
148153
dataFrame <- dataFrame[!precursorsToRemove, ]
149154

150155
numberOfRemovedIsotopePeaks <- sum(precursorsToRemove)
151156
numberOfPrecursors <- nrow(dataFrame)
152157
}
153-
158+
154159
if(!is.na(progress)) if(progress) incProgress(amount = 0, detail = paste("Boxing...", sep = "")) else print(paste("Boxing...", sep = ""))
155160
returnObj <- list()
156161
returnObj$dataFrame <- dataFrame
162+
returnObj$vals <- vals
157163

158164
## meta
159165
returnObj$oldFormat <- oldFormat

R/readMSDial.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -69,12 +69,12 @@ readMSDial <- function(file, version){
6969
rownames(counts) <- ids
7070

7171
# Ensure row names of colData match counts column names
72-
colData <- DataFrame(t(colDataRaw[-nrow(colDataRaw), -1]))
72+
colData <- data.frame(t(colDataRaw[-nrow(colDataRaw), -1]))
7373
rownames(colData) <- as.character(colDataRaw[nrow(colDataRaw), -1])
7474
colnames(colData) <- as.character(colDataRaw[-nrow(colDataRaw), 1])
7575

7676
# Ensure row names of rowData match counts row names
77-
rowData <- DataFrame(rowDataRaw[-1, ], row.names = ids)
77+
rowData <- data.frame(rowDataRaw[-1, ], row.names = ids)
7878
colnames(rowData) <- as.character(rowDataRaw[1,])
7979

8080
# Create SummarizedExperiment object

medint.Rdata

306 KB
Binary file not shown.

tests/testthat/IntMedDf.Rdata

308 KB
Binary file not shown.

tests/testthat/test-readMSDial.R

+6-4
Original file line numberDiff line numberDiff line change
@@ -7,13 +7,14 @@ test_that("exampledata", {
77
maximumRtDifference=0.05,
88
progress=FALSE)
99

10+
1011
## Test dimensions
11-
expect_equal(nrow(data$dataFrame1), 5403)
12-
expect_equal(ncol(data$dataFrame1), 20)
12+
expect_equal(nrow(data$dataFrame), 5403)
13+
expect_equal(ncol(data$dataFrame), 20)
1314

1415
## Test some values
15-
expect_true(all(summary(t(data$dataFrame1[1,c("TRI03", "TRI02", "TRI01", "LVS03", "LVS02", "LVS01")])) == c("Min. : 236.0 ", "1st Qu.: 306.2 ", "Median : 357.5 ", "Mean : 501.0 ", "3rd Qu.: 554.2 ", "Max. :1146.0 ")))
16-
expect_true(all(round(summary(data$dataFrame1[, "TRI01"])) == c(0, 809, 1537, 9818, 3207, 4407926)))
16+
expect_true(all(summary(t(data$dataFrame[1,c("TRI03", "TRI02", "TRI01", "LVS03", "LVS02", "LVS01")])) == c("Min. : 236.0 ", "1st Qu.: 306.2 ", "Median : 357.5 ", "Mean : 501.0 ", "3rd Qu.: 554.2 ", "Max. :1146.0 ")))
17+
expect_true(all(round(summary(data$dataFrame[, "TRI01"])) == c(0, 809, 1537, 9818, 3207, 4407926)))
1718
})
1819

1920

@@ -37,3 +38,4 @@ test_that("Number of Rows and Columns are correct", {
3738
})
3839

3940

41+

0 commit comments

Comments
 (0)