Skip to content

Commit 79d9c0c

Browse files
authored
account for missing injections in sbc (#30)
* dont supress warnings for knn * signal correction returns qc fit in processing history * batch correction uses correct order for samples
1 parent 9815c96 commit 79d9c0c

File tree

3 files changed

+23
-16
lines changed

3 files changed

+23
-16
lines changed

R/mv_imputation.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -131,7 +131,7 @@ mv_imputation <- function(df, method, k=10, rowmax=0.5, colmax=0.5,
131131
remove these columns using the sample filter tool")
132132
}
133133
if (tolower(method) == "knn") {
134-
obj <- suppressWarnings(impute.knn(assay(df), k=k,
134+
obj <- (impute.knn(assay(df), k=k,
135135
rowmax=rowmax, colmax=colmax, maxp=maxp))
136136
assay(df) <- obj$data
137137
} else if (tolower(method) == "rf") {

R/sbc_main.R

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,10 @@ QCRSC <- function(df, order, batch, classes, spar = 0, log = TRUE,
6666
log = log, spar = spar, batch = batch, minQC = minQC)
6767
QC_fit <- do.call(rbind, QC_fit)
6868

69+
meta_data <- metadata(df)
70+
meta_data$processing_history$QCRSC <- return_function_args()
71+
meta_data$processing_history$QCRSC$QC_fit=QC_fit
72+
6973
# Median value for each fature, and divide it by predicted value
7074
mpa <- matrixStats::rowMedians(assay(df), na.rm=TRUE)
7175
QC_fit <- QC_fit/mpa
@@ -74,8 +78,7 @@ QCRSC <- function(df, order, batch, classes, spar = 0, log = TRUE,
7478
assay(df) <- assay(df)/QC_fit
7579
assay(df)[assay(df) <= 0] <- NA
7680

77-
meta_data <- metadata(df)
78-
meta_data$processing_history$QCRSC <- return_function_args()
81+
7982
metadata(df) <- meta_data
8083
df <- return_original_data_structure(df)
8184

R/sbc_methods.R

Lines changed: 17 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -79,39 +79,43 @@ sbcWrapper <- function(id, qcData, order, qcBatch, qcOrder, log=log, spar=spar,
7979
batch=batch, minQC) {
8080

8181
out <- tryCatch ({
82-
# Measurment order can be non consecutive numbers as well
83-
maxOrder <- length(order)
84-
newOrder <- seq_len(maxOrder)
82+
83+
# qc data for feature
8584
subData <- qcData[id, ]
85+
86+
# unique batches
8687
nbatch <- unique(qcBatch)
8788

88-
outl <- matrix(nrow=maxOrder, ncol=length(nbatch))
89+
# preallocate output
90+
outl <- numeric(length(order))
8991

92+
# for each batch
9093
for (nb in seq_len(length(nbatch))) {
94+
# get the injection order for the QCs
9195
x <- qcOrder[qcBatch == nbatch[nb]]
96+
# get the response for the QCs
9297
y <- subData[qcBatch == nbatch[nb]]
98+
99+
# remove any index with NA in the response
93100
NAhits <- which(is.na(y))
94101

95102
if (length(NAhits) > 0) {
96103
x <- x[-c(NAhits)]
97104
y <- y[-c(NAhits)]
98105
}
99106

107+
# if we have enough QCs values
100108
if (length(y) >= minQC) {
101-
outl[,nb] <- splineSmoother(x=x, y=y, newX=newOrder, log=log,
109+
# fit spline to QCs and get predictions for all samples in batch
110+
outl[batch==nbatch[nb]] <- splineSmoother(x=x, y=y, newX=order[batch==nbatch[nb]], log=log,
102111
a=1, spar=spar)
103112
} else {
104-
outl[,nb] <- rep(NA, maxOrder)
113+
# otherwise replace with NA
114+
outl[batch==nbatch[nb]] = NA
105115
}
106116
}
107117

108-
outp <- rep(NA, nrow(outl))
109-
for (nb in seq_len(length(nbatch))) {
110-
range <- c(batch == nbatch[nb])
111-
outp[range] <- outl[range, nb]
112-
}
113-
114-
outp
118+
outp=outl
115119
},
116120

117121
error = function(e){

0 commit comments

Comments
 (0)