... | ... |
@@ -1,6 +1,8 @@ |
1 | 1 |
selectMulti <- function(measurementsTrain, classesTrain, params, verbose = 0) |
2 | 2 |
{ |
3 |
- assayTrain <- sapply(unique(S4Vectors::mcols(measurementsTrain)[["assay"]]), function(assay) measurementsTrain[, S4Vectors::mcols(measurementsTrain)[["assay"]] %in% assay], simplify = FALSE) |
|
3 |
+ assaysIndices <- lapply(unique(S4Vectors::mcols(measurementsTrain)[["assay"]]), function(assay) which(S4Vectors::mcols(measurementsTrain)[["assay"]] == assay)) |
|
4 |
+ assayTrain <- lapply(assaysIndices, function(assayIndices) measurementsTrain[, assayIndices]) |
|
5 |
+ |
|
4 | 6 |
featuresIndices <- mapply(.doSelection, |
5 | 7 |
measurements = assayTrain, |
6 | 8 |
modellingParams = params, |
... | ... |
@@ -8,7 +10,8 @@ selectMulti <- function(measurementsTrain, classesTrain, params, verbose = 0) |
8 | 10 |
crossValParams = CrossValParams(permutations = 1, folds = 5), ###### Where to get this from? |
9 | 11 |
verbose = 0), SIMPLIFY = FALSE |
10 | 12 |
) |
11 |
- |
|
12 |
- unique(unlist(lapply(featuresIndices, "[[", 2))) |
|
13 |
+ |
|
14 |
+ unlist(mapply(function(allDataIndices, withinIndices) allDataIndices[withinIndices], |
|
15 |
+ assaysIndices, lapply(featuresIndices, "[[", 2), SIMPLIFY = FALSE)) |
|
13 | 16 |
} |
14 | 17 |
attr(selectMulti, "name") <- "Union Selection" |
... | ... |
@@ -131,8 +131,8 @@ |
131 | 131 |
paramList <- append(paramList, tuneCombo) |
132 | 132 |
do.call(featureRanking, paramList) |
133 | 133 |
}) |
134 |
- |
|
135 |
- if(attr(featureRanking, "name") == "previousSelection") # Actually selection not ranking. |
|
134 |
+ |
|
135 |
+ if(attr(featureRanking, "name") %in% c("previousSelection", "Union Selection")) # Actually selection not ranking. |
|
136 | 136 |
return(list(NULL, rankings[[1]], NULL)) |
137 | 137 |
|
138 | 138 |
if(crossValParams@tuneMode == "none") # No parameters to choose between. |