Browse code

- ROCplot auto comparison choice now chooses most variable characteristic. - samplesMetricMap comparison default is now auto, in line with other plotting functions.

Dario Strbenac authored on 04/11/2022 02:35:05
Showing 4 changed files

... ...
@@ -86,4 +86,4 @@ Collate:
86 86
     'simpleParams.R'
87 87
     'subtractFromLocation.R'
88 88
     'utilities.R'
89
-URL: https://sydneybiox.github.io/ClassifyR/
90 89
\ No newline at end of file
90
+URL: https://sydneybiox.github.io/ClassifyR/
... ...
@@ -86,7 +86,7 @@ setMethod("ROCplot", "ClassifyResult", function(results, ...) {
86 86
 
87 87
 #' @rdname ROCplot
88 88
 #' @export
89
-setMethod("ROCplot", "list", 
89
+setMethod("ROCplot", "list",
90 90
           function(results, mode = c("merge", "average"), interval = 95,
91 91
                    comparison = "auto", lineColours = "auto",
92 92
                    lineWidth = 1, fontSizes = c(24, 16, 12, 12, 12), labelPositions = seq(0.0, 1.0, 0.2),
... ...
@@ -101,10 +101,18 @@ setMethod("ROCplot", "list",
101 101
   if(comparison == "auto")
102 102
   {
103 103
     if(max(characteristicsCounts) == length(results))
104
-      comparison <- names(characteristicsCounts)[characteristicsCounts == max(characteristicsCounts)][1]
105
-    else
104
+    { # Choose a characteristic which varies the most across the results.
105
+      candidates <- names(characteristicsCounts)[characteristicsCounts == length(results)]
106
+      allCharacteristics <- do.call(rbind, lapply(results, function(result) result@characteristics))
107
+      distinctValues <- by(allCharacteristics[, "value"], allCharacteristics[, "characteristic"], function(values) length(unique(values)))
108
+      comparison <- names(distinctValues)[which.max(distinctValues)][1]
109
+    } else {
106 110
       stop("No characteristic is present for all results but must be.")
111
+    }
107 112
   }
113
+  resultsWithComparison <- sum(sapply(results, function(result) any(result@characteristics[, "characteristic"] == comparison)))
114
+  if(resultsWithComparison < length(results))
115
+    stop("Not all results have comparison characteristic ", comparison, ' but need to.')
108 116
                
109 117
   ggplot2::theme_set(ggplot2::theme_classic() + ggplot2::theme(panel.border = ggplot2::element_rect(fill = NA)))
110 118
   distinctClasses <- levels(actualOutcome(results[[1]]))
... ...
@@ -13,7 +13,7 @@
13 13
 #' a matrix of pre-calculated metrics, for backwards compatibility.
14 14
 #' @param classes If \code{results} is a matrix, this is a factor vector of the
15 15
 #' same length as the number of columns that \code{results} has.
16
-#' @param comparison Default: "Classifier Name". The aspect of the experimental
16
+#' @param comparison Default: "auto". The aspect of the experimental
17 17
 #' design to compare. Can be any characteristic that all results share.
18 18
 #' @param metric Default: "Sample Error". The sample-wise metric to plot.
19 19
 #' @param featureValues If not NULL, can be a named factor or named numeric
... ...
@@ -82,11 +82,17 @@
82 82
 setGeneric("samplesMetricMap", function(results, ...)
83 83
 standardGeneric("samplesMetricMap"))
84 84
 
85
+#' @rdname samplesMetricMap
86
+#' @export
87
+setMethod("samplesMetricMap", "ClassifyResult", function(results, ...) {
88
+    samplesMetricMap(list(assay = results), ...)
89
+})
90
+
85 91
 #' @rdname samplesMetricMap
86 92
 #' @export
87 93
 setMethod("samplesMetricMap", "list", 
88 94
           function(results,
89
-                   comparison = "Classifier Name",
95
+                   comparison = "auto",
90 96
                    metric = c("Sample Error", "Sample Accuracy", "Sample C-index"),
91 97
                    featureValues = NULL, featureName = NULL,
92 98
                    metricColours = list(c("#3F48CC", "#6F75D8", "#9FA3E5", "#CFD1F2", "#FFFFFF"),
... ...
@@ -103,6 +109,20 @@ setMethod("samplesMetricMap", "list",
103 109
     stop("The package 'gridExtra' could not be found. Please install it.")       
104 110
   if(!requireNamespace("gtable", quietly = TRUE))
105 111
     stop("The package 'gtable' could not be found. Please install it.")
112
+  
113
+  characteristicsCounts <- table(unlist(lapply(results, function(result) result@characteristics[["characteristic"]])))
114
+  if(comparison == "auto")
115
+  {
116
+    if(max(characteristicsCounts) == length(results))
117
+    { # Choose a characteristic which varies the most across the results.
118
+      candidates <- names(characteristicsCounts)[characteristicsCounts == length(results)]
119
+      allCharacteristics <- do.call(rbind, lapply(results, function(result) result@characteristics))
120
+      distinctValues <- by(allCharacteristics[, "value"], allCharacteristics[, "characteristic"], function(values) length(unique(values)))
121
+      comparison <- names(distinctValues)[which.max(distinctValues)][1]
122
+    } else {
123
+      stop("No characteristic is present for all results but must be.")
124
+    }
125
+  }
106 126
   resultsWithComparison <- sum(sapply(results, function(result) any(result@characteristics[, "characteristic"] == comparison)))
107 127
   if(resultsWithComparison < length(results))
108 128
     stop("Not all results have comparison characteristic ", comparison, ' but need to.')
... ...
@@ -4,11 +4,14 @@
4 4
 \alias{samplesMetricMap}
5 5
 \alias{samplesMetricMap,list-method}
6 6
 \alias{samplesMetricMap,matrix-method}
7
+\alias{samplesMetricMap,ClassifyResult-method}
7 8
 \title{Plot a Grid of Sample Error Rates or Accuracies}
8 9
 \usage{
10
+\S4method{samplesMetricMap}{ClassifyResult}(results, ...)
11
+
9 12
 \S4method{samplesMetricMap}{list}(
10 13
   results,
11
-  comparison = "Classifier Name",
14
+  comparison = "auto",
12 15
   metric = c("Sample Error", "Sample Accuracy", "Sample C-index"),
13 16
   featureValues = NULL,
14 17
   featureName = NULL,
... ...
@@ -55,7 +58,7 @@
55 58
 \item{results}{A list of \code{\link{ClassifyResult}} objects. Could also be
56 59
 a matrix of pre-calculated metrics, for backwards compatibility.}
57 60
 
58
-\item{comparison}{Default: "Classifier Name". The aspect of the experimental
61
+\item{comparison}{Default: "auto". The aspect of the experimental
59 62
 design to compare. Can be any characteristic that all results share.}
60 63
 
61 64
 \item{metric}{Default: "Sample Error". The sample-wise metric to plot.}