Having problem with colnames when making DataFrame from list
... | ... |
@@ -381,6 +381,7 @@ setMethod("crossValidate", "matrix", # Matrix of numeric measurements. |
381 | 381 |
# This expects that each table is about the same set of samples and thus |
382 | 382 |
# has the same number of rows as every other table. |
383 | 383 |
#' @rdname crossValidate |
384 |
+#' @importFrom S4Vectors combineRows |
|
384 | 385 |
#' @export |
385 | 386 |
setMethod("crossValidate", "list", |
386 | 387 |
function(measurements, |
... | ... |
@@ -425,7 +426,13 @@ setMethod("crossValidate", "list", |
425 | 426 |
}, df_list, names(df_list)) |
426 | 427 |
|
427 | 428 |
|
428 |
- combined_df <- do.call(cbind, df_list) |
|
429 |
+ # combined_df <- do.call("cbind", df_list) was adding the list names to the colnames |
|
430 |
+ |
|
431 |
+ combined_df <- df_list[[1]] |
|
432 |
+ for(i in names(df_list)[-1]){ |
|
433 |
+ combined_df <- S4Vectors::combineRows(combined_df, df_list[[i]], use.names=FALSE) |
|
434 |
+ } |
|
435 |
+ |
|
429 | 436 |
|
430 | 437 |
crossValidate(measurements = combined_df, |
431 | 438 |
outcome = outcome, |
... | ... |
@@ -1069,4 +1076,4 @@ predict.trainedByClassifyR <- function(object, newData, ...) |
1069 | 1076 |
} else if (is(object, "listOfModels")) { # Object is itself a trained model and it is assumed that a predict method is defined for it. |
1070 | 1077 |
mapply(function(model, assay) predict(model, assay), object, newData, SIMPLIFY = FALSE) |
1071 | 1078 |
} else predict(object, newData) |
1072 |
-} |
|
1073 | 1079 |
\ No newline at end of file |
1080 |
+} |