Browse code

- Added prediction function for precusion pathway. - Added calcCostsAndPerformance, summary, bubblePlot, flowchart, and strataPlot evaluation functions for precision pathways.

Dario Strbenac authored on 20/02/2023 06:10:15
Showing 6 changed files

... ...
@@ -4,7 +4,7 @@ Title: A framework for cross-validated classification problems, with
4 4
        applications to differential variability and differential
5 5
        distribution testing
6 6
 Version: 3.3.14
7
-Date: 2023-02-16
7
+Date: 2023-02-20
8 8
 Authors@R:
9 9
     c(
10 10
     person(given = "Dario", family = "Strbenac", email = "dario.strbenac@sydney.edu.au", role = c("aut", "cre")),
... ...
@@ -24,7 +24,7 @@ Imports: grid, genefilter, utils, dplyr, tidyr, rlang, ranger, ggplot2 (>= 3.0.0
24 24
 Suggests: limma, edgeR, car, Rmixmod, gridExtra (>= 2.0.0), cowplot,
25 25
         BiocStyle, pamr, PoiClaClu, parathyroidSE, knitr, htmltools, gtable,
26 26
         scales, e1071, rmarkdown, IRanges, robustbase, glmnet, class, randomForestSRC,
27
-        MatrixModels, xgboost
27
+        MatrixModels, xgboost, data.tree, ggnewscale
28 28
 Description: The software formalises a framework for classification and survival model evaluation
29 29
              in R. There are four stages; Data transformation, feature selection, model training,
30 30
              and prediction. The requirements of variable types and variable order are
... ...
@@ -1,6 +1,7 @@
1 1
 # Generated by roxygen2: do not edit by hand
2 2
 
3 3
 S3method(predict,trainedByClassifyR)
4
+S3method(summary,PrecisionPathways)
4 5
 S3method(train,DataFrame)
5 6
 S3method(train,MultiAssayExperiment)
6 7
 S3method(train,data.frame)
... ...
@@ -18,7 +19,9 @@ export(TransformParams)
18 19
 export(actualOutcome)
19 20
 export(allFeatureNames)
20 21
 export(available)
22
+export(bubblePlot.PrecisionPathways)
21 23
 export(calcCVperformance)
24
+export(calcCostsAndPerformance)
22 25
 export(calcExternalPerformance)
23 26
 export(chosenFeatureNames)
24 27
 export(colCoxTests)
... ...
@@ -29,6 +32,7 @@ export(distribution)
29 32
 export(edgesToHubNetworks)
30 33
 export(featureSetSummary)
31 34
 export(finalModel)
35
+export(flowchart.PrecisionPathways)
32 36
 export(interactorDifferences)
33 37
 export(models)
34 38
 export(performance)
... ...
@@ -42,6 +46,7 @@ export(runTests)
42 46
 export(sampleNames)
43 47
 export(samplesMetricMap)
44 48
 export(selectionPlot)
49
+export(strataPlot.PrecisionPathways)
45 50
 export(totalPredictions)
46 51
 export(tunedParameters)
47 52
 exportClasses(ClassifyResult)
... ...
@@ -8,6 +8,7 @@
8 8
 #
9 9
 ################################################################################
10 10
 
11
+setOldClass("PrecisionPathways")
11 12
 
12 13
 # Union of A Function and NULL
13 14
 setClassUnion("functionOrNULL", c("function", "NULL"))
... ...
@@ -26,7 +26,7 @@
26 26
 #' @param nFolds A numeric specifying the number of folds to use for cross-validation.
27 27
 #' @param nRepeats A numeric specifying the the number of repeats or permutations to use for cross-validation.
28 28
 #' @param nCores A numeric specifying the number of cores used if the user wants to use parallelisation.
29
-#' @param pathways A set of pathways created by \code{precisionPathwaysTrain} to be used for predicting on a new data set.
29
+#' @param pathways A set of pathways created by \code{precisionPathwaysTrain} which is an object of class \code{PrecisionPathways} to be used for predicting on a new data set.
30 30
 #' @rdname precisionPathways
31 31
 #' @return An object of class \code{PrecisionPathways} which is basically a named list that other plotting and
32 32
 #' tabulating functions can use.
... ...
@@ -57,7 +57,7 @@ setMethod("precisionPathwaysTrain", "MultiAssayExperimentOrList",
57 57
             measurementsAndClass <- do.call(prepareData, prepArgs)
58 58
               
59 59
             .precisionPathwaysTrain(measurementsAndClass[["measurements"]], measurementsAndClass[["outcome"]],
60
-                                   fixedAssays = fixedAssays, confidenceCutoff = confidenceCutoff,
60
+                                   clinicalPredictors = clinicalPredictors, fixedAssays = fixedAssays, confidenceCutoff = confidenceCutoff,
61 61
                                    minAssaySamples = minAssaySamples, nFeatures = nFeatures,
62 62
                                    selectionMethod = selectionMethod, classifier = classifier,
63 63
                                    nFolds = nFolds, nRepeats = nRepeats, nCores = nCores)
... ...
@@ -66,7 +66,7 @@ setMethod("precisionPathwaysTrain", "MultiAssayExperimentOrList",
66 66
 # Internal method which carries out all of the processing, obtaining reformatted data from the
67 67
 # MultiAssayExperiment and list (of basic rectangular tables) S4 methods.
68 68
 .precisionPathwaysTrain <- function(measurements, class, fixedAssays = "clinical",
69
-                   confidenceCutoff = 0.8, minAssaySamples = 10,
69
+                   clinicalPredictors = clinicalPredictors, confidenceCutoff = 0.8, minAssaySamples = 10,
70 70
                    nFeatures = 20, selectionMethod = setNames(c(NULL, rep("t-test", length(measurements))), c("clinical", names(measurements))),
71 71
                    classifier = setNames(c("elasticNetGLM", rep("randomForest", length(measurements))), c("clinical", names(measurements))),
72 72
                    nFolds = 5, nRepeats = 20, nCores = 1)
... ...
@@ -101,6 +101,7 @@ setMethod("precisionPathwaysTrain", "MultiAssayExperimentOrList",
101 101
                 predictionsSamplesCounts <- table(allPredictions[, "sample"], allPredictions[, "class"])
102 102
                 confidences <- 2 * abs(predictionsSamplesCounts[, 1] / rowSums(predictionsSamplesCounts) - 0.5)
103 103
                 sampleIDsUse <- names(confidences)[confidences > confidenceCutoff]
104
+                sampleIDsUse <- setdiff(sampleIDsUse, samplesUsed)
104 105
                 
105 106
                 # Check if too few samples left for next round. Include them in this round, if so.
106 107
                 remainingIDs <- setdiff(allSampleIDs, c(samplesUsed, sampleIDsUse))
... ...
@@ -134,14 +135,17 @@ setMethod("precisionPathwaysTrain", "MultiAssayExperimentOrList",
134 135
                 if(breakEarly == TRUE) break
135 136
               }
136 137
               pathwayString <- paste(assaysProcessed, collapse = '-')
137
-              parameters = list(confidenceCutoff = confidenceCutoff, minAssaySamples = minAssaySamples)
138
-              list(models = modelsList, parameters = parameters, pathway = pathwayString,
138
+              individualsTableAll[, "Tier"] <- factor(individualsTableAll[, "Tier"], levels = permutation)
139
+              list(pathway = pathwayString,
139 140
                   individuals = individualsTableAll, tiers = tierTableAll)
140 141
             })
141
-            
142
-            class(precisionPathways) <- "PrecisionPathways"
143 142
             names(precisionPathways) <- sapply(precisionPathways, "[[", "pathway")
144
-            precisionPathways
143
+            result <- list(models = modelsList, assaysPermutations = assaysPermutations,
144
+                           parameters = list(confidenceCutoff = confidenceCutoff, minAssaySamples = minAssaySamples),
145
+                           clinicalPredictors = clinicalPredictors, pathways = precisionPathways)
146
+            class(result) <- "PrecisionPathways"
147
+            
148
+            result
145 149
 }
146 150
 
147 151
 # A nice print method to avoid flooding the screen with lots of tables
... ...
@@ -150,7 +154,7 @@ print.PrecisionPathways <- function(x)
150 154
 {
151 155
   cat("An object of class 'PrecisionPathways'.\n")
152 156
   cat("Pathways:\n")
153
-  cat(paste(names(x), collapse = '\n'))
157
+  cat(paste(names(x[["pathways"]]), collapse = '\n'))
154 158
 }
155 159
 
156 160
 #' @usage NULL
... ...
@@ -159,7 +163,7 @@ setGeneric("precisionPathwaysPredict", function(pathways, measurements, class, .
159 163
 
160 164
 #' @rdname precisionPathways
161 165
 #' @export
162
-setMethod("precisionPathwaysPredict", "MultiAssayExperimentOrList", 
166
+setMethod("precisionPathwaysPredict", c("PrecisionPathways", "MultiAssayExperimentOrList"), 
163 167
           function(pathways, measurements, class)
164 168
           {
165 169
             if(is.list(measurements)) # Ensure plain list has clinical data.
... ...
@@ -168,7 +172,8 @@ setMethod("precisionPathwaysPredict", "MultiAssayExperimentOrList",
168 172
               if (!any(names(measurements) == "clinical"))
169 173
                 stop("One of the tables must be named \"clinical\".")
170 174
             }
171
-            prepArgs <- list(measurements, outcomeColumns = class)
175
+
176
+            prepArgs <- list(measurements, outcomeColumns = class, clinicalPredictors = pathways[["clinicalPredictors"]])
172 177
             measurementsAndClass <- do.call(prepareData, prepArgs)
173 178
               
174 179
             .precisionPathwaysPredict(pathways, measurementsAndClass[["measurements"]], measurementsAndClass[["outcome"]])
... ...
@@ -176,5 +181,259 @@ setMethod("precisionPathwaysPredict", "MultiAssayExperimentOrList",
176 181
 
177 182
 .precisionPathwaysPredict <- function(pathways, measurements, class)
178 183
 {
179
-  # To do.
184
+
185
+  # Step 1: Extract all of previously fitted models and permutations.
186
+  modelsList <- pathways[["models"]]
187
+  assayIDs <- lapply(PPT[["models"]], function(model) model@characteristics[model@characteristics[, 1] == "Assay Name", 2])
188
+  assaysPermutations <- pathways[["assaysPermutations"]]
189
+  confidenceCutoff <- pathways[["parameters"]][["confidenceCutoff"]]
190
+  minAssaySamples <- pathways[["parameters"]][["minAssaySamples"]]
191
+  
192
+  # Step 2: Loop over each pathway and each assay in order to determine which samples are used at that level
193
+  # and which are passed onwards.
194
+  precisionPathways <- lapply(as.data.frame(assaysPermutations), function(permutation)
195
+  {
196
+    assaysProcessed <- character()
197
+    samplesUsed <- character()
198
+    individualsTableAll <- S4Vectors::DataFrame()
199
+    tierTableAll <- S4Vectors::DataFrame()
200
+    breakEarly = FALSE
201
+    for(assay in permutation)
202
+    {
203
+      # Step 2a: Identify all samples which are consistently predicted.
204
+      modelIndex <- match(assay, assayIDs)
205
+      allPredictions <- predictions(modelsList[[modelIndex]])
206
+      allSampleIDs <- sampleNames(modelsList[[modelIndex]])
207
+      predictionsSamplesCounts <- table(allPredictions[, "sample"], allPredictions[, "class"])
208
+      confidences <- 2 * abs(predictionsSamplesCounts[, 1] / rowSums(predictionsSamplesCounts) - 0.5)
209
+      sampleIDsUse <- names(confidences)[confidences > confidenceCutoff]
210
+      sampleIDsUse <- setdiff(sampleIDsUse, samplesUsed)
211
+                
212
+      # Check if too few samples left for next round. Include them in this round, if so.
213
+      remainingIDs <- setdiff(allSampleIDs, c(samplesUsed, sampleIDsUse))
214
+      if(length(remainingIDs) < minAssaySamples)
215
+      {
216
+        sampleIDsUse <- c(sampleIDsUse, remainingIDs)
217
+        breakEarly = TRUE
218
+      } else { }
219
+                
220
+      predictionsSamplesCounts <- predictionsSamplesCounts[sampleIDsUse, ]
221
+                
222
+      # Step 2b: Individuals predictions and sample-wise accuracy, tier-wise error.
223
+      maxVotes <- apply(predictionsSamplesCounts, 1, function(sample) which.max(sample))
224
+      predictedClasses <- factor(colnames(predictionsSamplesCounts)[maxVotes],
225
+                                 levels = colnames(predictionsSamplesCounts))    
226
+      individualsTable <- S4Vectors::DataFrame(Tier = assay,
227
+                                               `Sample ID` = sampleIDsUse,
228
+                                               `Predicted` = predictedClasses,
229
+                                               `Accuracy` = performance(modelsList[[modelIndex]])[["Sample Accuracy"]][sampleIDsUse],
230
+                                                check.names = FALSE)
231
+      knownClasses <- actualOutcome(modelsList[[modelIndex]])[match(sampleIDsUse, allSampleIDs)]
232
+      balancedAccuracy <- calcExternalPerformance(knownClasses, predictedClasses)
233
+      tierTable <- S4Vectors::DataFrame(Tier = assay,
234
+                                        `Balanced Accuracy` = balancedAccuracy, check.names = FALSE)
235
+                
236
+      assaysProcessed <- c(assaysProcessed, assay)
237
+      individualsTableAll <- rbind(individualsTableAll, individualsTable)
238
+      tierTableAll <- rbind(tierTableAll, tierTable)
239
+      samplesUsed <- c(samplesUsed, sampleIDsUse)
240
+                
241
+      if(breakEarly == TRUE) break
242
+    }
243
+    pathwayString <- paste(assaysProcessed, collapse = '-')
244
+    individualsTableAll[, "Tier"] <- factor(individualsTableAll[, "Tier"], levels = permutation)
245
+    list(pathway = pathwayString,
246
+         individuals = individualsTableAll, tiers = tierTableAll)
247
+  })
248
+  names(precisionPathways) <- sapply(precisionPathways, "[[", "pathway")
249
+  result <- list(models = modelsList, assaysPermutations = assaysPermutations,
250
+                 parameters = list(confidenceCutoff = confidenceCutoff, minAssaySamples = minAssaySamples),
251
+                 clinicalPredictors = clinicalPredictors, pathways = precisionPathways)
252
+  class(result) <- "PrecisionPathways"
253
+            
254
+  result
255
+}
256
+
257
+# Calculate accuracy and costs of each pathway.
258
+
259
+#' Various Functions for Evaluating Precision Pathways
260
+#' 
261
+#' These functions tabulate or plot various aspects of precision pathways, such as accuracies and costs.
262
+#' 
263
+#' @param precisionPathways A pathway of class \code{PrecisionPathways}.
264
+#' @param costs A named vector of assays with the cost of each one.
265
+#' @rdname precisionPathwaysEvaluations
266
+#' @export
267
+calcCostsAndPerformance <- function(precisionPathways, costs = NULL)
268
+{
269
+  if(is.null(costs))
270
+    stop("'costs' of each assay must be specified.")      
271
+  pathwayIDs <- names(precisionPathways[["pathways"]])
272
+  accuraciesCosts <- do.call(rbind, lapply(precisionPathways[["pathways"]], function(pathway)
273
+  {
274
+    predictions <- pathway[["individuals"]][, "Predicted"]
275
+    knownClasses <- actualOutcome(precisionPathways$models[[1]])
276
+    allNames <- sampleNames(precisionPathways$models[[1]])
277
+    knownClasses <- knownClasses[match(pathway[["individuals"]][, "Sample ID"], allNames)]
278
+    balancedAccuracy <- calcExternalPerformance(knownClasses, predictions)
279
+    
280
+    costTotal <- sum(costs[match(pathway[["individuals"]][, "Tier"], names(costs))])
281
+    
282
+    data.frame(accuracy = round(balancedAccuracy, 2), cost = costTotal)
283
+  }))
284
+
285
+  precisionPathways$performance <- accuraciesCosts
286
+  precisionPathways
287
+}
288
+
289
+# Print a summary table, including accuracy and costs.
290
+
291
+#' @param object A set of pathways of class \code{PrecisionPathways}.
292
+#' @param weights A numeric vector of length two specifying how to weight the predictive accuracy
293
+#' and the cost during ranking. Must sum to 1.
294
+#' @rdname precisionPathwaysEvaluations
295
+#' @export
296
+summary.PrecisionPathways <- function(object, weights = c(accuracy = 0.5, cost = 0.5))
297
+{
298
+  summaryTable <- data.frame(Pathway = rownames(object[["performance"]]),
299
+                             `Balanced Accuracy` = object[["performance"]][, "accuracy"],
300
+                             `Total Cost` = object[["performance"]][, "cost"],
301
+                              check.names = FALSE)
302
+  rankingScores <- list(rank(object[["performance"]][, "accuracy"]), rank(-object[["performance"]][, "cost"]))
303
+  finalScores <- rowSums(mapply(function(scores, weight)
304
+               {
305
+                 scores * weight
306
+               }, rankingScores, as.list(weights)))
307
+  summaryTable <- cbind(summaryTable, Score = finalScores)
308
+  summaryTable
309
+}
310
+
311
+#' @param precisionPathways A pathway of class \code{PrecisionPathways}.
312
+#' @param pathwayColours A named vector of colours with names being the names of pathways. If none is specified,
313
+#' a default colour scheme will automatically be chosen.
314
+#' @rdname precisionPathwaysEvaluations
315
+#' @export
316
+bubblePlot.PrecisionPathways <- function(precisionPathways, pathwayColours = NULL)
317
+{
318
+  ggplot2::theme_set(ggplot2::theme_classic() + ggplot2::theme(panel.border = ggplot2::element_rect(fill = NA)))    
319
+  if(is.null(pathwayColours)) pathwayColours <- scales::hue_pal()(length(precisionPathways[["pathways"]]))
320
+  performance <- precisionPathways[["performance"]]
321
+  performance <- cbind(Sequence = rownames(performance), performance)
322
+  ggplot2::ggplot(performance, aes(x = accuracy, y = cost, colour = Sequence)) + geom_point() +
323
+    ggplot2::scale_color_manual(values = pathwayColours) + labs(x = "Balanced Accuracy", y = "Total Cost")
324
+}
325
+
326
+#' @param precisionPathways A pathway of class \code{PrecisionPathways}.
327
+#' @param pathway A chracter vector of length 1 specifying which pathway to plot, e.g. "clinical-mRNA".
328
+#' @param nodeColours A named vector of colours with names being \code{"assay"}, \code{"class1"},\code{"class2"}.
329
+#' a default colour scheme will automatically be chosen.
330
+#' @rdname precisionPathwaysEvaluations
331
+#' @export
332
+flowchart.PrecisionPathways <- function(precisionPathways, pathway, nodeColours = c(assay = "#86C57C", class1 = "#ACCEE0", class2 = "#F47F72"))
333
+{
334
+  if(!requireNamespace("data.tree", quietly = TRUE))
335
+    stop("The package 'data.tree' could not be found. Please install it.")
336
+
337
+  pathwayUse <- precisionPathways[["pathways"]][[pathway]]
338
+  assayIDs <- pathwayUse[["tiers"]][, 1]
339
+  possibleClasses <- levels(precisionPathways$models[[1]]@actualOutcome)
340
+  samplesTiers <- pathwayUse$individuals
341
+      
342
+  pathwayTree <- Node$new(assayIDs[1])
343
+  currentNode <- pathwayTree
344
+  for(assay in assayIDs)
345
+  {
346
+    toDo <- nrow(samplesTiers) - max(which(samplesTiers[, "Tier"] == assay))
347
+    class1Predictions <- currentNode$AddChild(possibleClasses[1], counter = nrow(subset(samplesTiers, Predicted == possibleClasses[1] & Tier == assay)), nodeType = "Class1")
348
+    uncertain <- currentNode$AddChild("Uncertain", counter = toDo, nodeType = "Uncertain")
349
+    class2Predictions = currentNode$AddChild(possibleClasses[2], counter = nrow(subset(samplesTiers, Predicted == possibleClasses[2] & Tier == assay)), nodeType = "Class2")
350
+    
351
+    if(toDo == 0) {break} else {
352
+      currentNode <- uncertain
353
+      currentNode <- currentNode$AddChild(assayIDs[match(assay, assayIDs) + 1], nodeType = "Platform")
354
+    }
355
+  }
356
+          
357
+  SetGraphStyle(pathwayTree, rankdir = "LR")
358
+  SetEdgeStyle(pathwayTree, fontname = 'helvetica', label = .getEdgeLabel)
359
+  SetNodeStyle(pathwayTree, style = "filled", shape = .getNodeShape, fontcolor = "black", fillcolor = .getFillColour, fontname = 'helvetica')
360
+  plot(pathwayTree)
361
+}
362
+
363
+.getEdgeLabel <- function(node)
364
+{
365
+  nSamples <<- nrow(samplesTiers)
366
+  if(node$isRoot || node$nodeType == "Platform")
367
+  {
368
+    label <- NULL
369
+  } else {
370
+    value <- round((node$counter / nSamples) * 100)
371
+    label <- paste(value,  "% (", node$counter, ")", sep = '')
372
+  }
373
+  return(label)
374
+}
375
+
376
+.getNodeShape <- function(node){
377
+  if(node$isRoot || node$nodeType == "Platform"){
378
+    shape = "oval"
379
+  } else {
380
+    shape = "box"
381
+  }
382
+}
383
+
384
+.getFillColour <- function(node) {
385
+  if(node$isRoot || node$nodeType == "Platform"){
386
+    colour <<- nodeColours[["assay"]]
387
+  } else if(node$nodeType == "Class1"){
388
+    colour <<- nodeColours[["class1"]]
389
+  } else if(node$nodeType == "Class2"){
390
+    colour <<- nodeColours[["class2"]]
391
+  } else {
392
+    colour = "snow3"
393
+  }
394
+  return(colour)
395
+}
396
+
397
+
398
+#' @param classColours A named vector of colours with names being \code{"class1"},\code{"class2"}, and \code{"accuracy"}.
399
+#' a default colour scheme will automatically be chosen.
400
+#' @rdname precisionPathwaysEvaluations
401
+#' @export
402
+strataPlot.PrecisionPathways <- function(precisionPathways, pathway, classColours = c(class1 = "#4DAF4A", class2 = "#984EA3"))
403
+{
404
+  pathwayUse <- precisionPathways[["pathways"]][[pathway]]
405
+  assayIDs <- pathwayUse[["tiers"]][, 1]
406
+  possibleClasses <- levels(precisionPathways$models[[1]]@actualOutcome)
407
+  samplesTiers <- pathwayUse$individuals
408
+  samplesTiers$trueClass <- actualOutcome(precisionPathways$models[[1]])[match(samplesTiers[, "Sample ID"], sampleNames(precisionPathways$models[[1]]))]
409
+  samplesTiers <- dplyr::arrange(as.data.frame(samplesTiers), Tier, trueClass, Accuracy)
410
+  samplesTiers$ID = 1:nrow(samplesTiers)
411
+  samplesTiers$colour = ifelse(samplesTiers$trueClass == levels(samplesTiers[, "Predicted"])[1], classColours["class1"], classColours["class2"])
412
+
413
+  strataPlot <- ggplot(mapping = aes(x = ID, y = Tier), data = samplesTiers) +
414
+                geom_tile(aes(fill = trueClass)) +
415
+    scale_fill_manual(values = unname(classColours))  +
416
+    labs(title = paste("Pathway:", pathway), fill = "True Class", x = "", y = "") +
417
+    guides(fill = guide_legend(title.position = "top")) +
418
+    ggnewscale::new_scale_fill() +
419
+    geom_tile(aes(fill = Accuracy)) +
420
+    scale_fill_gradient(low = "#377EB8", high = "#E41A1C") +
421
+    labs(fill = "Accuracy") +
422
+    guides(fill = guide_colorbar(title.position = "top")) +
423
+    theme(panel.background = element_blank(),
424
+          axis.text.x = element_blank(),
425
+          aspect.ratio = 1/4, 
426
+          plot.title = element_text(face = "bold", size = 20),
427
+          legend.title = element_text(face = "bold", size = 12),
428
+          legend.text = element_text(size = 10),
429
+          legend.position = "bottom",
430
+          axis.text = element_text(size = 15)) +
431
+    annotate("tile",
432
+               x = samplesTiers$ID,
433
+               y = length(levels(samplesTiers[, "Tier"])) + 0.8,
434
+               height = 0.6,
435
+               fill = samplesTiers$colour)  +
436
+    coord_cartesian(expand = FALSE) 
437
+    
438
+  strataPlot
180 439
 }
181 440
\ No newline at end of file
... ...
@@ -3,7 +3,7 @@
3 3
 \name{precisionPathwaysTrain}
4 4
 \alias{precisionPathwaysTrain}
5 5
 \alias{precisionPathwaysTrain,MultiAssayExperimentOrList-method}
6
-\alias{precisionPathwaysPredict,MultiAssayExperimentOrList-method}
6
+\alias{precisionPathwaysPredict,PrecisionPathways,MultiAssayExperimentOrList-method}
7 7
 \title{Precision Pathways for Sample Prediction Based on Prediction Confidence.}
8 8
 \usage{
9 9
 \S4method{precisionPathwaysTrain}{MultiAssayExperimentOrList}(
... ...
@@ -25,7 +25,7 @@
25 25
   nCores = 1
26 26
 )
27 27
 
28
-\S4method{precisionPathwaysPredict}{MultiAssayExperimentOrList}(pathways, measurements, class)
28
+\S4method{precisionPathwaysPredict}{PrecisionPathways,MultiAssayExperimentOrList}(pathways, measurements, class)
29 29
 }
30 30
 \arguments{
31 31
 \item{measurements}{Either a \code{\link{MultiAssayExperiment}} or a list of the basic tabular objects containing the data.}
... ...
@@ -63,7 +63,7 @@ would have less than this number of samples, the samples are incorporated into t
63 63
 
64 64
 \item{nCores}{A numeric specifying the number of cores used if the user wants to use parallelisation.}
65 65
 
66
-\item{pathways}{A set of pathways created by \code{precisionPathwaysTrain} to be used for predicting on a new data set.}
66
+\item{pathways}{A set of pathways created by \code{precisionPathwaysTrain} which is an object of class \code{PrecisionPathways} to be used for predicting on a new data set.}
67 67
 }
68 68
 \value{
69 69
 An object of class \code{PrecisionPathways} which is basically a named list that other plotting and
70 70
new file mode 100644
... ...
@@ -0,0 +1,52 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/precisionPathways.R
3
+\name{calcCostsAndPerformance}
4
+\alias{calcCostsAndPerformance}
5
+\alias{summary.PrecisionPathways}
6
+\alias{bubblePlot.PrecisionPathways}
7
+\alias{flowchart.PrecisionPathways}
8
+\alias{strataPlot.PrecisionPathways}
9
+\title{Various Functions for Evaluating Precision Pathways}
10
+\usage{
11
+calcCostsAndPerformance(precisionPathways, costs = NULL)
12
+
13
+\method{summary}{PrecisionPathways}(object, weights = c(accuracy = 0.5, cost = 0.5))
14
+
15
+bubblePlot.PrecisionPathways(precisionPathways, pathwayColours = NULL)
16
+
17
+flowchart.PrecisionPathways(
18
+  precisionPathways,
19
+  pathway,
20
+  nodeColours = c(assay = "#86C57C", class1 = "#ACCEE0", class2 = "#F47F72")
21
+)
22
+
23
+strataPlot.PrecisionPathways(
24
+  precisionPathways,
25
+  pathway,
26
+  classColours = c(class1 = "#4DAF4A", class2 = "#984EA3")
27
+)
28
+}
29
+\arguments{
30
+\item{precisionPathways}{A pathway of class \code{PrecisionPathways}.}
31
+
32
+\item{costs}{A named vector of assays with the cost of each one.}
33
+
34
+\item{object}{A set of pathways of class \code{PrecisionPathways}.}
35
+
36
+\item{weights}{A numeric vector of length two specifying how to weight the predictive accuracy
37
+and the cost during ranking. Must sum to 1.}
38
+
39
+\item{pathwayColours}{A named vector of colours with names being the names of pathways. If none is specified,
40
+a default colour scheme will automatically be chosen.}
41
+
42
+\item{pathway}{A chracter vector of length 1 specifying which pathway to plot, e.g. "clinical-mRNA".}
43
+
44
+\item{nodeColours}{A named vector of colours with names being \code{"assay"}, \code{"class1"},\code{"class2"}.
45
+a default colour scheme will automatically be chosen.}
46
+
47
+\item{classColours}{A named vector of colours with names being \code{"class1"},\code{"class2"}, and \code{"accuracy"}.
48
+a default colour scheme will automatically be chosen.}
49
+}
50
+\description{
51
+These functions tabulate or plot various aspects of precision pathways, such as accuracies and costs.
52
+}