... | ... |
@@ -431,7 +431,7 @@ setMethod("crossValidate", "list", |
431 | 431 |
} |
432 | 432 |
|
433 | 433 |
# Check the number of outcome is the same |
434 |
- if ((measurements[[1]] |> dim())[1] != length(outcome)) { |
|
434 |
+ if (((measurements[[1]] |> dim())[1] != length(outcome)) & length(outcome)>2) { |
|
435 | 435 |
stop("outcome must have same number of samples as measurements") |
436 | 436 |
} |
437 | 437 |
|
... | ... |
@@ -913,4 +913,4 @@ setMethod("predict", "ClassifyResult", |
913 | 913 |
function(object, newData) |
914 | 914 |
{ |
915 | 915 |
object@modellingParams@predictParams@predictor(object@finalModel[[1]], newData) |
916 |
- }) |
|
917 | 916 |
\ No newline at end of file |
917 |
+ }) |
... | ... |
@@ -56,7 +56,7 @@ setMethod("prevalTrainInterface", "DFrame", |
56 | 56 |
### |
57 | 57 |
# Splitting measurements into a list of each of the assays |
58 | 58 |
### |
59 |
- assayTrain <- sapply(unique(mcols(measurements)[["assay"]]), function(assay) measurements[, mcols(measurements)[["dataset"]] %in% assay], simplify = FALSE) |
|
59 |
+ assayTrain <- sapply(unique(mcols(measurements)[["assay"]]), function(assay) measurements[, mcols(measurements)[["assay"]] %in% assay], simplify = FALSE) |
|
60 | 60 |
|
61 | 61 |
if(!"clinical" %in% names(assayTrain)) stop("Must have an assay called \"clinical\"") |
62 | 62 |
|
... | ... |
@@ -72,7 +72,7 @@ setMethod("prevalTrainInterface", "DFrame", |
72 | 72 |
measurements = assayTrain[usePreval], |
73 | 73 |
modellingParams = params[usePreval], |
74 | 74 |
MoreArgs = list( |
75 |
- classes = classes, |
|
75 |
+ outcome = classes, |
|
76 | 76 |
crossValParams = CVparams, |
77 | 77 |
verbose = 0 |
78 | 78 |
), |
... | ... |
@@ -98,7 +98,7 @@ setMethod("prevalTrainInterface", "DFrame", |
98 | 98 |
#fullTrain = cbind(assayTrain[["clinical"]][,selectedFeaturesClinical], prevalidationTrain[rownames(assayTrain[["clinical"]]), , drop = FALSE]) |
99 | 99 |
|
100 | 100 |
prevalidationTrain <- S4Vectors::DataFrame(prevalidationTrain) |
101 |
- mcols(prevalidationTrain)$assay = "PCA" |
|
101 |
+ mcols(prevalidationTrain)$assay = "prevalidation" |
|
102 | 102 |
mcols(prevalidationTrain)$feature = colnames(prevalidationTrain) |
103 | 103 |
|
104 | 104 |
|
... | ... |
@@ -116,10 +116,10 @@ setMethod("prevalTrainInterface", "DFrame", |
116 | 116 |
|
117 | 117 |
# Fit classification model (from clinical in params) |
118 | 118 |
runTestOutput = runTest( |
119 |
- fullTrain, |
|
120 |
- classes = classes, |
|
121 |
- training = seq_len(nrow(fullTrain)), |
|
122 |
- testing = seq_len(nrow(fullTrain)), |
|
119 |
+ measurementsTrain = fullTrain, |
|
120 |
+ outcomeTrain = classes, |
|
121 |
+ measurementsTest = fullTrain, |
|
122 |
+ outcomeTest = classes, |
|
123 | 123 |
modellingParams = finalModParam, |
124 | 124 |
crossValParams = CVparams, |
125 | 125 |
.iteration = 1, |
... | ... |
@@ -134,12 +134,12 @@ setMethod("prevalTrainInterface", "DFrame", |
134 | 134 |
# Fit models with each datatype for use in prevalidated prediction later.. |
135 | 135 |
prevalidationModels = mapply( |
136 | 136 |
runTest, |
137 |
- measurements = assayTrain[usePreval], |
|
137 |
+ measurementsTrain = assayTrain[usePreval], |
|
138 |
+ outcomeTrain = classes, |
|
139 |
+ measurementsTest = assayTrain[usePreval], |
|
140 |
+ outTest = classes, |
|
138 | 141 |
modellingParams = params[usePreval], |
139 | 142 |
MoreArgs = list( |
140 |
- classes = classes, |
|
141 |
- training = seq_len(nrow(fullTrain)), |
|
142 |
- testing = seq_len(nrow(fullTrain)), |
|
143 | 143 |
crossValParams = CVparams, |
144 | 144 |
.iteration = 1, |
145 | 145 |
verbose = 0 |
... | ... |
@@ -191,7 +191,7 @@ setMethod("prevalPredictInterface", c("prevalModel", "DFrame"), |
191 | 191 |
extractPrevalidation() |
192 | 192 |
|
193 | 193 |
prevalidationPredict <- S4Vectors::DataFrame(prevalidationPredict) |
194 |
- mcols(prevalidationPredict)$assay = "PCA" |
|
194 |
+ mcols(prevalidationPredict)$assay = "prevalidation" |
|
195 | 195 |
mcols(prevalidationPredict)$feature = colnames(prevalidationPredict) |
196 | 196 |
|
197 | 197 |
fullTest = cbind(assayTest[["clinical"]], prevalidationPredict[rownames(assayTest[["clinical"]]), , drop = FALSE]) |
... | ... |
@@ -117,8 +117,8 @@ function(measurementsTrain, outcomeTrain, measurementsTest, outcomeTest, |
117 | 117 |
featuresInfo <- .summaryFeatures(measurementsTrain) |
118 | 118 |
if(!is.null(S4Vectors::mcols(measurementsTrain))) |
119 | 119 |
{ |
120 |
- S4Vectors::mcols(measurementsTrain) <- featuresInfo[, c("Renamed Assay", "Renamed Feature")] |
|
121 |
- S4Vectors::mcols(measurementsTest) <- featuresInfo[, c("Renamed Assay", "Renamed Feature")] |
|
120 |
+ #S4Vectors::mcols(measurementsTrain) <- featuresInfo[, c("Renamed Assay", "Renamed Feature")] |
|
121 |
+ #S4Vectors::mcols(measurementsTest) <- featuresInfo[, c("Renamed Assay", "Renamed Feature")] |
|
122 | 122 |
colnames(measurementsTrain) <- colnames(measurementsTest) <- paste(featuresInfo[["Renamed Assay"]], featuresInfo[["Renamed Feature"]], sep = '') |
123 | 123 |
} else { |
124 | 124 |
colnames(measurementsTrain) <- colnames(measurementsTest) <- featuresInfo[, "Renamed Feature"] |
... | ... |
@@ -330,4 +330,4 @@ setMethod("runTest", c("MultiAssayExperiment"), |
330 | 330 |
tablesAndClassesTest <- .MAEtoWideTable(measurementsTest, targets, outcomeColumns, restrict = NULL) |
331 | 331 |
runTest(tablesAndClassesTrain[["dataTable"]], tablesAndClassesTrain[["outcome"]], |
332 | 332 |
tablesAndClassesTest[["dataTable"]], tablesAndClassesTest[["outcome"]], ...) |
333 |
-}) |
|
334 | 333 |
\ No newline at end of file |
334 |
+}) |
... | ... |
@@ -586,7 +586,7 @@ |
586 | 586 |
featuresInfo <- S4Vectors::DataFrame(originalFeatures, renamedInfo) |
587 | 587 |
colnames(featuresInfo) <- c("Original Feature", "Renamed Feature") |
588 | 588 |
} |
589 |
- featuresInfo |
|
589 |
+ cbind(originalInfo, featuresInfo) |
|
590 | 590 |
} |
591 | 591 |
|
592 | 592 |
# Function to identify the parameters of an S4 method. |
... | ... |
@@ -776,4 +776,4 @@ |
776 | 776 |
|
777 | 777 |
.dmvnorm_diag <- function(x, mean, sigma) { # Remove once sparsediscrim is reinstated to CRAN. |
778 | 778 |
exp(sum(dnorm(x, mean=mean, sd=sqrt(sigma), log=TRUE))) |
779 |
-} |
|
780 | 779 |
\ No newline at end of file |
780 |
+} |