Browse code

Merge pull request #53 from SydneyBioX/master

Recent fixes and improvements

Dario Strbenac authored on 17/11/2022 09:43:39 • GitHub committed on 17/11/2022 09:43:39
Showing 135 changed files

... ...
@@ -1,2 +1,10 @@
1
-^.*\.Rproj$
2
-^\.Rproj\.user$
1
+^.*\.Rproj$
2
+^\.Rproj\.user$
3
+^_pkgdown\.yml$
4
+^docs$
5
+^pkgdown$
6
+vignettes/introduction.Rmd
7
+vignettes/performanceEvaluation.Rmd
8
+vignettes/multiViewMethods.Rmd
9
+vignettes/incorporateNew.Rmd
10
+^\.github$
... ...
@@ -1,4 +1,8 @@
1
-.Rproj.user
2
-.Rhistory
3
-.RData
4
-.Ruserdata
1
+.Rproj.user
2
+.Rhistory
3
+.RData
4
+.Ruserdata
5
+
6
+
7
+# vscode stuff
8
+.vscode
5 9
\ No newline at end of file
... ...
@@ -3,10 +3,19 @@ Type: Package
3 3
 Title: A framework for cross-validated classification problems, with
4 4
        applications to differential variability and differential
5 5
        distribution testing
6
-Version: 3.3.0
7
-Date: 2022-10-25
8
-Author: Dario Strbenac, Ellis Patrick, Sourish Iyengar, Harry Robertson, Andy Tran, John Ormerod, Graham Mann, Jean Yang
9
-Maintainer: Dario Strbenac <dario.strbenac@sydney.edu.au>
6
+Version: 3.3.3
7
+Date: 2022-11-17
8
+Authors@R:
9
+    c(
10
+    person(given = "Dario", family = "Strbenac", email = "dario.strbenac@sydney.edu.au", role = c("aut", "cre")),
11
+    person(given = "Ellis", family = "Patrick", role = "aut"),
12
+    person(given = "Sourish", family = "Iyengar", role = "aut"),
13
+    person(given = "Harry", family = "Robertson", role = "aut"),
14
+    person(given = "Andy", family = "Tran", role = "aut"),
15
+    person(given = "John", family = "Ormerod", role = "aut"),
16
+    person(given = "Graham", family = "Mann", role = "aut"),
17
+    person(given = "Jean", family = "Yang", email = "jean.yang@sydney.edu.au", role = "aut")
18
+    )
10 19
 VignetteBuilder: knitr
11 20
 Encoding: UTF-8
12 21
 biocViews: Classification, Survival
... ...
@@ -86,3 +95,4 @@ Collate:
86 95
     'simpleParams.R'
87 96
     'subtractFromLocation.R'
88 97
     'utilities.R'
98
+URL: https://sydneybiox.github.io/ClassifyR/
... ...
@@ -27,8 +27,6 @@ export(distribution)
27 27
 export(edgesToHubNetworks)
28 28
 export(featureSetSummary)
29 29
 export(finalModel)
30
-export(generateCrossValParams)
31
-export(generateModellingParams)
32 30
 export(interactorDifferences)
33 31
 export(models)
34 32
 export(performance)
... ...
@@ -87,7 +85,6 @@ exportMethods(selectionPlot)
87 85
 exportMethods(show)
88 86
 exportMethods(totalPredictions)
89 87
 exportMethods(tunedParameters)
90
-import(BiocParallel)
91 88
 import(MultiAssayExperiment)
92 89
 import(grid)
93 90
 import(methods)
... ...
@@ -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]]))
... ...
@@ -113,6 +113,15 @@ setMethod("calcExternalPerformance", c("Surv", "numeric"),
113 113
             .calcPerformance(actualOutcome, predictedOutcome, performanceType = performanceType)[["values"]]
114 114
           })
115 115
 
116
+#' @rdname calcPerformance
117
+#' @exportMethod calcExternalPerformance
118
+setMethod("calcExternalPerformance", c("factor", "tabular"), # table has class probabilities per sample.
119
+          function(actualOutcome, predictedOutcome, performanceType = "AUC")
120
+          {
121
+            performanceType <- match.arg(performanceType)
122
+            .calcPerformance(actualOutcome, predictedOutcome, performanceType = performanceType)[["values"]]
123
+          })
124
+
116 125
 #' @rdname calcPerformance
117 126
 #' @usage NULL
118 127
 #' @export
... ...
@@ -11,22 +11,26 @@
11 11
 #' same length as the number of samples in \code{measurements} or a character vector of length 1 containing the
12 12
 #' column name in \code{measurements} if it is a \code{\link{DataFrame}}. Or a \code{\link{Surv}} object or a character vector of
13 13
 #' length 2 or 3 specifying the time and event columns in \code{measurements} for survival outcome. If \code{measurements} is a
14
-#' \code{\link{MultiAssayExperiment}}, the column name(s) in \code{colData(measurements)} representing the outcome.
14
+#' \code{\link{MultiAssayExperiment}}, the column name(s) in \code{colData(measurements)} representing the outcome.  If column names
15
+#' of survival information, time must be in first column and event status in the second.
15 16
 #' @param outcomeTrain For the \code{train} function, either a factor vector of classes, a \code{\link{Surv}} object, or
16 17
 #' a character string, or vector of such strings, containing column name(s) of column(s)
17
-#' containing either classes or time and event information about survival.
18
+#' containing either classes or time and event information about survival. If column names
19
+#' of survival information, time must be in first column and event status in the second.
18 20
 #' @param ... Parameters passed into \code{\link{prepareData}} which control subsetting and filtering of input data.
19 21
 #' @param nFeatures The number of features to be used for classification. If this is a single number, the same number of features will be used for all comparisons
20 22
 #' or assays. If a numeric vector these will be optimised over using \code{selectionOptimisation}. If a named vector with the same names of multiple assays, 
21 23
 #' a different number of features will be used for each assay. If a named list of vectors, the respective number of features will be optimised over. 
22 24
 #' Set to NULL or "all" if all features should be used.
23
-#' @param selectionMethod A character vector of feature selection methods to compare. If a named character vector with names corresponding to different assays, 
24
-#' and performing multiview classification, the respective classification methods will be used on each assay.
25
+#' @param selectionMethod Default: "auto". A character vector of feature selection methods to compare. If a named character vector with names corresponding to different assays, 
26
+#' and performing multiview classification, the respective classification methods will be used on each assay. If \code{"auto"} t-test (two categories) / F-test (three or more categories) ranking
27
+#' and top \code{nFeatures} optimisation is done. Otherwise, the ranking method is per-feature Cox proportional hazards p-value.
25 28
 #' @param selectionOptimisation A character of "Resubstitution", "Nested CV" or "none" specifying the approach used to optimise \code{nFeatures}.
26
-#' @param performanceType Default: \code{"auto"}. If \code{"auto"}, then balanced accuracy for classification or C-index for survival. Any one of the
29
+#' @param performanceType Default: \code{"auto"}. If \code{"auto"}, then balanced accuracy for classification or C-index for survival. Otherwise, any one of the
27 30
 #' options described in \code{\link{calcPerformance}} may otherwise be specified.
28
-#' @param classifier A character vector of classification methods to compare. If a named character vector with names corresponding to different assays, 
29
-#' and performing multiview classification, the respective classification methods will be used on each assay.
31
+#' @param classifier Default: \code{"auto"}. A character vector of classification methods to compare. If a named character vector with names corresponding to different assays, 
32
+#' and performing multiview classification, the respective classification methods will be used on each assay. If \code{"auto"}, then a random forest is used for a classification
33
+#' task or Cox proportional hazards model for a survival task.
30 34
 #' @param multiViewMethod A character vector specifying the multiview method or data integration approach to use.
31 35
 #' @param assayCombinations A character vector or list of character vectors proposing the assays or, in the case of a list, combination of assays to use
32 36
 #' with each element being a vector of assays to combine. Special value \code{"all"} means all possible subsets of assays.
... ...
@@ -108,12 +112,14 @@ setMethod("crossValidate", "DataFrame",
108 112
               if(!performanceType %in% c("auto", .ClassifyRenvir[["performanceTypes"]]))
109 113
                 stop(paste("performanceType must be one of", paste(c("auto", .ClassifyRenvir[["performanceTypes"]]), collapse = ", "), "but is", performanceType))
110 114
               
115
+              isCategorical <- is.character(outcome) && (length(outcome) == 1 || length(outcome) == nrow(measurements)) || is.factor(outcome)
111 116
               if(performanceType == "auto")
112
-              {
113
-                if(is.character(outcome) && (length(outcome) == 1 || length(outcome) == nrow(measurements)) || is.factor(outcome))
114
-                  performanceType <- "Balanced Accuracy"
115
-                else performanceType <- "C-index"
116
-              }
117
+                if(isCategorical) performanceType <- "Balanced Accuracy" else performanceType <- "C-index"
118
+              if(length(selectionMethod) == 1 && selectionMethod == "auto")
119
+                if(isCategorical) selectionMethod <- "t-test" else selectionMethod <- "CoxPH"
120
+              if(length(classifier) == 1 && classifier == "auto")
121
+                if(isCategorical) classifier <- "randomForest" else classifier <- "CoxPH"
122
+              
117 123
               
118 124
               # Which data-types or data-views are present?
119 125
               assayIDs <- unique(S4Vectors::mcols(measurements)$assay)
... ...
@@ -515,18 +521,6 @@ Using an ordinary GLM instead.")
515 521
     classifier
516 522
 }
517 523
 
518
-######################################
519
-######################################
520
-#' A function to generate a CrossValParams object
521
-#'
522
-#' @inheritParams crossValidate
523
-#'
524
-#' @return CrossValParams object
525
-#' @export
526
-#'
527
-#' @examples
528
-#' CVparams <- generateCrossValParams(nRepeats = 20, nFolds = 5, nCores = 8, selectionOptimisation = "none")
529
-#' @import BiocParallel
530 524
 generateCrossValParams <- function(nRepeats, nFolds, nCores, selectionOptimisation){
531 525
 
532 526
     seed <- .Random.seed[1]
... ...
@@ -549,32 +543,7 @@ generateCrossValParams <- function(nRepeats, nFolds, nCores, selectionOptimisati
549 543
     if(!any(tuneMode %in% c("Resubstitution", "Nested CV", "none"))) stop("selectionOptimisation must be Nested CV or Resubstitution or none")
550 544
     CrossValParams(permutations = nRepeats, folds = nFolds, parallelParams = BPparam, tuneMode = tuneMode)
551 545
 }
552
-######################################
553 546
 
554
-######################################
555
-#' A function to generate a ModellingParams object
556
-#'
557
-#' @inheritParams crossValidate
558
-#' @param assayIDs A vector of data set identifiers as long at the number of data sets.
559
-#'
560
-#' @return ModellingParams object
561
-#' @export
562
-#'
563
-#' @examples
564
-#' data(asthma)
565
-#' # First make a toy example assay with multiple data types. We'll randomly assign different features to be clinical, gene or protein.
566
-#' set.seed(51773)
567
-#' measurements <- DataFrame(measurements, check.names = FALSE) 
568
-#' mcols(measurements)$assay <- c(rep("clinical",20),sample(c("gene", "protein"), ncol(measurements)-20, replace = TRUE))
569
-#' mcols(measurements)$feature <- colnames(measurements)
570
-#' modellingParams <- generateModellingParams(assayIDs = c("clinical", "gene", "protein"),
571
-#'                                           measurements = measurements, 
572
-#'                                           nFeatures = list(clinical = 10, gene = 10, protein = 10),
573
-#'                                           selectionMethod = list(clinical = "t-test", gene = "t-test", protein = "t-test"),
574
-#'                                           selectionOptimisation = "none",
575
-#'                                           classifier = "randomForest",
576
-#'                                           multiViewMethod = "merge")
577
-#' @import BiocParallel
578 547
 generateModellingParams <- function(assayIDs,
579 548
                                     measurements,
580 549
                                     nFeatures,
... ...
@@ -6,9 +6,11 @@ randomForestTrainInterface <- function(measurementsTrain, outcomeTrain, mTryProp
6 6
   if(verbose == 3)
7 7
     message("Fitting random forest classifier to training data.")
8 8
   mtry <- round(mTryProportion * ncol(measurementsTrain)) # Number of features to try.
9
-      
10 9
   # Convert to base data.frame as randomForest doesn't understand DataFrame.
11
-  ranger::ranger(x = as(measurementsTrain, "data.frame"), y = outcomeTrain, mtry = mtry, importance = "impurity_corrected", ...)
10
+  fittedModel <- ranger::ranger(x = as(measurementsTrain, "data.frame"), y = outcomeTrain, mtry = mtry, ...)
11
+  forImportance <- ranger::ranger(x = as(measurementsTrain, "data.frame"), y = outcomeTrain, mtry = mtry, importance = "impurity_corrected", ...)
12
+  attr(fittedModel, "forImportance") <- forImportance
13
+  fittedModel
12 14
 }
13 15
 attr(randomForestTrainInterface, "name") <- "randomForestTrainInterface"
14 16
     
... ...
@@ -37,7 +39,8 @@ randomForestPredictInterface <- function(forest, measurementsTest, ..., returnTy
37 39
 
38 40
 forestFeatures <- function(forest)
39 41
                   {
40
-                    rankedFeaturesIndices <- order(ranger::importance(forest), decreasing = TRUE)
41
-                    selectedFeaturesIndices <- which(ranger::importance(forest) > 0)
42
+                    forImportance <- attr(forest, "forImportance")
43
+                    rankedFeaturesIndices <- order(ranger::importance(forImportance), decreasing = TRUE)
44
+                    selectedFeaturesIndices <- which(ranger::importance(forImportance) > 0)
42 45
                     list(rankedFeaturesIndices, selectedFeaturesIndices)
43 46
                   }
44 47
\ No newline at end of file
... ...
@@ -5,8 +5,9 @@ rfsrcTrainInterface <- function(measurementsTrain, survivalTrain, mTryProportion
5 5
     stop("The package 'randomForestSRC' could not be found. Please install it.")
6 6
   if(verbose == 3)
7 7
     message("Fitting rfsrc classifier to training data and making predictions on test data.")
8
-    
9
-  bindedMeasurements <- cbind(measurementsTrain, event = survivalTrain[, 1], time = survivalTrain[, 2])
8
+
9
+  # Surv objects store survival information as a two-column table, time and event, in that order.    
10
+  bindedMeasurements <- cbind(measurementsTrain, time = survivalTrain[, 1], event = survivalTrain[, 2])
10 11
   mtry <- round(mTryProportion * ncol(measurementsTrain)) # Number of features to try.
11 12
   randomForestSRC::rfsrc(Surv(time, event) ~ ., data = as.data.frame(bindedMeasurements), mtry = mtry,
12 13
                           var.used = "all.trees", importance = TRUE, ...)
... ...
@@ -13,7 +13,8 @@
13 13
 #' are features.
14 14
 #' @param outcome Either a factor vector of classes, a \code{\link{Surv}} object, or
15 15
 #' a character string, or vector of such strings, containing column name(s) of column(s)
16
-#' containing either classes or time and event information about survival.
16
+#' containing either classes or time and event information about survival. If column names
17
+#' of survival information, time must be in first column and event status in the second.
17 18
 #' @param outcomeColumns If \code{measurements} is a \code{MultiAssayExperiment}, the
18 19
 #' names of the column (class) or columns (survival) in the table extracted by \code{colData(data)}
19 20
 #' that contain(s) the each individual's outcome to use for prediction.
... ...
@@ -4,7 +4,7 @@ coxphRanking <- function(measurementsTrain, survivalTrain, verbose = 3) # Clinic
4 4
   
5 5
   pValues <- rep(NA, ncol(measurementsTrain))
6 6
   names(pValues) <- colnames(measurementsTrain)
7
-  
7
+
8 8
   isCat <- sapply(measurementsTrain, class) %in% c("character", "factor")
9 9
   if(any(isCat))
10 10
   {
... ...
@@ -16,7 +16,8 @@
16 16
 #' \code{matrix} or \code{\link{DataFrame}}, the rows are samples, and the columns are features.
17 17
 #' @param outcomeTrain Either a factor vector of classes, a \code{\link{Surv}} object, or
18 18
 #' a character string, or vector of such strings, containing column name(s) of column(s)
19
-#' containing either classes or time and event information about survival.
19
+#' containing either classes or time and event information about survival. If column names
20
+#' of survival information, time must be in first column and event status in the second.
20 21
 #' @param measurementsTest Same data type as \code{measurementsTrain}, but only the test
21 22
 #' samples.
22 23
 #' @param outcomeTest Same data type as \code{outcomeTrain}, but for only the test
... ...
@@ -256,12 +257,19 @@ input data. Autmomatically reducing to smaller number.")
256 257
     {
257 258
       if(is.null(modellingParams@trainParams@getFeatures))
258 259
       selectedFeatures <- originalFeatures[selectedFeaturesIndices]
259
-      else selectedFeatures <- colnames(measurementsTrain)[rankedFeaturesIndices] 
260
+      else selectedFeatures <- colnames(measurementsTrain)[selectedFeaturesIndices] 
260 261
     } else {
261 262
       featureColumns <- na.omit(match(c("assay", "feature"), colnames(S4Vectors::mcols(measurementsTrain))))
262
-      if(is.null(modellingParams@trainParams@getFeatures))
263
-      selectedFeatures <- originalFeatures[selectedFeaturesIndices, ]
264
-      else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]
263
+      if(length(featureColumns) == 1)
264
+      {
265
+         if(is.null(modellingParams@trainParams@getFeatures))
266
+            selectedFeatures <- originalFeatures[selectedFeaturesIndices]
267
+         else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]            
268
+      } else {
269
+                if(is.null(modellingParams@trainParams@getFeatures))
270
+                  selectedFeatures <- originalFeatures[selectedFeaturesIndices, ]
271
+                else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]            
272
+      }
265 273
     }
266 274
     importanceTable <- S4Vectors::DataFrame(selectedFeatures, performanceChanges)
267 275
     if(ncol(importanceTable) == 2) colnames(importanceTable)[1] <- "feature"
... ...
@@ -272,6 +280,7 @@ input data. Autmomatically reducing to smaller number.")
272 280
   if(!is.null(tuneDetailsSelect)) tuneDetails <- tuneDetailsSelect else tuneDetails <- tuneDetailsTrain
273 281
 
274 282
   # Convert back into original, potentially unsafe feature identifiers unless it is a nested cross-validation.
283
+  
275 284
   if(is.null(.iteration) || .iteration != "internal")
276 285
   {
277 286
     if(!is.null(rankedFeaturesIndices))
... ...
@@ -283,9 +292,16 @@ input data. Autmomatically reducing to smaller number.")
283 292
         else rankedFeatures <- colnames(measurementsTrain)[rankedFeaturesIndices]            
284 293
       } else {
285 294
         featureColumns <- na.omit(match(c("assay", "feature"), colnames(S4Vectors::mcols(measurementsTrain))))          
286
-        if(is.null(modellingParams@trainParams@getFeatures))
287
-          rankedFeatures <- originalFeatures[rankedFeaturesIndices, ]
288
-        else rankedFeatures <- S4Vectors::mcols(measurementsTrain)[rankedFeaturesIndices, featureColumns]
295
+        if(length(featureColumns) == 1)
296
+        {
297
+          if(is.null(modellingParams@trainParams@getFeatures))
298
+            rankedFeatures <- originalFeatures[rankedFeaturesIndices]
299
+          else rankedFeatures <- S4Vectors::mcols(measurementsTrain)[rankedFeaturesIndices, featureColumns]
300
+        } else {
301
+          if(is.null(modellingParams@trainParams@getFeatures))
302
+            rankedFeatures <- originalFeatures[rankedFeaturesIndices, ]
303
+          else rankedFeatures <- S4Vectors::mcols(measurementsTrain)[rankedFeaturesIndices, featureColumns] 
304
+        }
289 305
       }
290 306
     } else { rankedFeatures <- NULL}
291 307
     if(!is.null(selectedFeaturesIndices))
... ...
@@ -297,9 +313,16 @@ input data. Autmomatically reducing to smaller number.")
297 313
         else selectedFeatures <- colnames(measurementsTrain)[selectedFeaturesIndices]
298 314
       } else {
299 315
         featureColumns <- na.omit(match(c("assay", "feature"), colnames(S4Vectors::mcols(measurementsTrain))))  
300
-        if(is.null(modellingParams@trainParams@getFeatures))
301
-          selectedFeatures <- originalFeatures[selectedFeaturesIndices, ]
302
-        else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]
316
+        if(length(featureColumns) == 1)
317
+        {
318
+          if(is.null(modellingParams@trainParams@getFeatures))
319
+            selectedFeatures <- originalFeatures[selectedFeaturesIndices]
320
+          else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]            
321
+        } else {
322
+                if(is.null(modellingParams@trainParams@getFeatures))
323
+                  selectedFeatures <- originalFeatures[selectedFeaturesIndices, ]
324
+                else selectedFeatures <- S4Vectors::mcols(measurementsTrain)[selectedFeaturesIndices, featureColumns]            
325
+        }
303 326
       }
304 327
     } else { selectedFeatures <- NULL}
305 328
   } else { # Nested use in feature selection. No feature selection in inner execution, so ignore features. 
... ...
@@ -16,7 +16,8 @@
16 16
 #' containing either classes or time and event information about survival. If
17 17
 #' \code{measurements} is a \code{MultiAssayExperiment}, the names of the column (class) or
18 18
 #' columns (survival) in the table extracted by \code{colData(data)} that contain(s) the samples'
19
-#' outcome to use for prediction.
19
+#' outcome to use for prediction. If column names of survival information, time must be in first
20
+#' column and event status in the second.
20 21
 #' @param crossValParams An object of class \code{\link{CrossValParams}},
21 22
 #' specifying the kind of cross-validation to be done.
22 23
 #' @param modellingParams An object of class \code{\link{ModellingParams}},
... ...
@@ -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
... ...
@@ -44,6 +44,8 @@
44 44
 #' @param legendSize The size of the boxes in the legends.
45 45
 #' @param plot Logical. IF \code{TRUE}, a plot is produced on the current
46 46
 #' graphics device.
47
+#' @param ... Parameters not used by the \code{ClassifyResult} method that does
48
+#' list-packaging but used by the main \code{list} method.
47 49
 #' @return A plot is produced and a grob is returned that can be saved to a
48 50
 #' graphics device.
49 51
 #' @author Dario Strbenac
... ...
@@ -82,11 +84,17 @@
82 84
 setGeneric("samplesMetricMap", function(results, ...)
83 85
 standardGeneric("samplesMetricMap"))
84 86
 
87
+#' @rdname samplesMetricMap
88
+#' @export
89
+setMethod("samplesMetricMap", "ClassifyResult", function(results, ...) {
90
+    samplesMetricMap(list(assay = results), ...)
91
+})
92
+
85 93
 #' @rdname samplesMetricMap
86 94
 #' @export
87 95
 setMethod("samplesMetricMap", "list", 
88 96
           function(results,
89
-                   comparison = "Classifier Name",
97
+                   comparison = "auto",
90 98
                    metric = c("Sample Error", "Sample Accuracy", "Sample C-index"),
91 99
                    featureValues = NULL, featureName = NULL,
92 100
                    metricColours = list(c("#3F48CC", "#6F75D8", "#9FA3E5", "#CFD1F2", "#FFFFFF"),
... ...
@@ -103,6 +111,20 @@ setMethod("samplesMetricMap", "list",
103 111
     stop("The package 'gridExtra' could not be found. Please install it.")       
104 112
   if(!requireNamespace("gtable", quietly = TRUE))
105 113
     stop("The package 'gtable' could not be found. Please install it.")
114
+  
115
+  characteristicsCounts <- table(unlist(lapply(results, function(result) result@characteristics[["characteristic"]])))
116
+  if(comparison == "auto")
117
+  {
118
+    if(max(characteristicsCounts) == length(results))
119
+    { # Choose a characteristic which varies the most across the results.
120
+      candidates <- names(characteristicsCounts)[characteristicsCounts == length(results)]
121
+      allCharacteristics <- do.call(rbind, lapply(results, function(result) result@characteristics))
122
+      distinctValues <- by(allCharacteristics[, "value"], allCharacteristics[, "characteristic"], function(values) length(unique(values)))
123
+      comparison <- names(distinctValues)[which.max(distinctValues)][1]
124
+    } else {
125
+      stop("No characteristic is present for all results but must be.")
126
+    }
127
+  }
106 128
   resultsWithComparison <- sum(sapply(results, function(result) any(result@characteristics[, "characteristic"] == comparison)))
107 129
   if(resultsWithComparison < length(results))
108 130
     stop("Not all results have comparison characteristic ", comparison, ' but need to.')
109 131
new file mode 100644
... ...
@@ -0,0 +1,25 @@
1
+# ClassifyR: Performance evaluation for multi-view data sets and seamless integration with MultiAssayExperiment and Bioconductor
2
+
3
+<img src="man/figures/ClassifyRsticker.png" align="right" width=250 style="margin-left: 10px;">
4
+
5
+ClassifyR's performance evaluation focuses on model stability and interpretability. Based on repeated cross-validation, it is possible to evaluate feature selection stability and also per-sample prediction accuracy. Also, multiple omics data assays on the same samples are becoming more popular and ClassifyR supports a range of multi-view methods to evaluate which data view is the most predictive and combine data views to evaluate if multiple views provide superior predictive performance to a single data view.
6
+
7
+##  Installation 
8
+
9
+The recommended method of installing ClassifyR is by using Bioconductor's BiocManager installer:
10
+
11
+```
12
+library(BiocManager)
13
+install("ClassifyR", dependencies = TRUE)
14
+```
15
+
16
+The above code will install all packages that provide feature selection or model-building functionality. If only one or two methods are desired then the dependencies option could be omitted and those packages providing functionality installed manually. 
17
+ 
18
+##  Website
19
+
20
+Please visit [the ClassifyR website](https://sydneybiox.github.io/ClassifyR/) to view the main vignette as well as articles that provide more in-depth explanations for various aspects of the package. Details of performance evaluation, multi-view methods and contributing a wrapper for a new algorithm to the package are provided.
21
+
22
+
23
+## Reference
24
+
25
+Strbenac D., Mann, G.J., Ormerod, J.T., and Yang, J. Y. H. (2015) ClassifyR: An R package for performance assessment of classification with applications to transcriptomics, *Bioinformatics*.
0 26
new file mode 100644
... ...
@@ -0,0 +1,15 @@
1
+url: https://sydneybiox.github.io/ClassifyR/
2
+template:
3
+  bootstrap: 5
4
+articles:
5
+- title: Menu
6
+  contents:
7
+    - introduction
8
+    - performanceEvaluation
9
+    - multiViewMethods
10
+    - incorporateNew
11
+    - ClassifyR
12
+    - DevelopersGuide
13
+navbar:
14
+  title: ~
15
+  bg: dark
0 16
new file mode 100644
... ...
@@ -0,0 +1,86 @@
1
+<!DOCTYPE html>
2
+<!-- Generated by pkgdown: do not edit by hand --><html lang="en">
3
+<head>
4
+<meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
5
+<meta charset="utf-8">
6
+<meta http-equiv="X-UA-Compatible" content="IE=edge">
7
+<meta name="viewport" content="width=device-width, initial-scale=1, shrink-to-fit=no">
8
+<title>Page not found (404) • ClassifyR</title>
9
+<script src="https://sydneybiox.github.io/ClassifyR/deps/jquery-3.6.0/jquery-3.6.0.min.js"></script><meta name="viewport" content="width=device-width, initial-scale=1, shrink-to-fit=no">
10
+<link href="https://sydneybiox.github.io/ClassifyR/deps/bootstrap-5.1.3/bootstrap.min.css" rel="stylesheet">
11
+<script src="https://sydneybiox.github.io/ClassifyR/deps/bootstrap-5.1.3/bootstrap.bundle.min.js"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous">
12
+<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous">
13
+<!-- bootstrap-toc --><script src="https://cdn.rawgit.com/afeld/bootstrap-toc/v1.0.1/dist/bootstrap-toc.min.js"></script><!-- headroom.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script><!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script><!-- search --><script src="https://cdnjs.cloudflare.com/ajax/libs/fuse.js/6.4.6/fuse.js" integrity="sha512-zv6Ywkjyktsohkbp9bb45V6tEMoWhzFzXis+LrMehmJZZSys19Yxf1dopHx7WzIKxr5tK2dVcYmaCk2uqdjF4A==" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/autocomplete.js/0.38.0/autocomplete.jquery.min.js" integrity="sha512-GU9ayf+66Xx2TmpxqJpliWbT5PiGYxpaG8rfnBEk1LL8l1KGkRShhngwdXK1UgqhAzWpZHSiYPc09/NwDQIGyg==" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mark.js/8.11.1/mark.min.js" integrity="sha512-5CYOlHXGh6QpOFA/TeTylKLWfB3ftPsde7AnmhuitiTX4K5SqCLBeKro6sPS8ilsz1Q4NRx3v8Ko2IBiszzdww==" crossorigin="anonymous"></script><!-- pkgdown --><script src="https://sydneybiox.github.io/ClassifyR/pkgdown.js"></script><meta property="og:title" content="Page not found (404)">
14
+<!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]>
15
+<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
16
+<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
17
+<![endif]-->
18
+</head>
19
+<body>
20
+    <a href="https://sydneybiox.github.io/ClassifyR/#main" class="visually-hidden-focusable">Skip to contents</a>
21
+    
22
+
23
+    <nav class="navbar fixed-top navbar-dark navbar-expand-lg bg-dark"><div class="container">
24
+    
25
+    <a class="navbar-brand me-2" href="https://sydneybiox.github.io/ClassifyR/index.html">ClassifyR</a>
26
+
27
+    <small class="nav-text text-muted me-auto" data-bs-toggle="tooltip" data-bs-placement="bottom" title="">3.3.2</small>
28
+
29
+    
30
+    <button class="navbar-toggler" type="button" data-bs-toggle="collapse" data-bs-target="#navbar" aria-controls="navbar" aria-expanded="false" aria-label="Toggle navigation">
31
+      <span class="navbar-toggler-icon"></span>
32
+    </button>
33
+
34
+    <div id="navbar" class="collapse navbar-collapse ms-3">
35
+      <ul class="navbar-nav me-auto">
36
+<li class="nav-item">
37
+  <a class="nav-link" href="https://sydneybiox.github.io/ClassifyR/articles/ClassifyR.html">Get started</a>
38
+</li>
39
+<li class="nav-item">
40
+  <a class="nav-link" href="https://sydneybiox.github.io/ClassifyR/reference/index.html">Reference</a>
41
+</li>
42
+<li class="nav-item">
43
+  <a class="nav-link" href="https://sydneybiox.github.io/ClassifyR/articles/index.html">Articles</a>
44
+</li>
45
+      </ul>
46
+<form class="form-inline my-2 my-lg-0" role="search">
47
+        <input type="search" class="form-control me-sm-2" aria-label="Toggle navigation" name="search-input" data-search-index="search.json" id="search-input" placeholder="Search for" autocomplete="off">
48
+</form>
49
+
50
+      <ul class="navbar-nav"></ul>
51
+</div>
52
+
53
+    
54
+  </div>
55
+</nav><div class="container template-title-body">
56
+<div class="row">
57
+  <main id="main" class="col-md-9"><div class="page-header">
58
+      <img src="https://sydneybiox.github.io/ClassifyR/" class="logo" alt=""><h1>Page not found (404)</h1>
59
+      
60
+    </div>
61
+
62
+Content not found. Please use links in the navbar.
63
+
64
+  </main>
65
+</div>
66
+
67
+
68
+    <footer><div class="pkgdown-footer-left">
69
+  <p></p>
70
+<p>Developed by Dario Strbenac, Ellis Patrick, Sourish Iyengar, Harry Robertson, Andy Tran, John Ormerod, Graham Mann, Jean Yang.</p>
71
+</div>
72
+
73
+<div class="pkgdown-footer-right">
74
+  <p></p>
75
+<p>Site built with <a href="https://pkgdown.r-lib.org/" class="external-link">pkgdown</a> 2.0.6.</p>
76
+</div>
77
+
78
+    </footer>
79
+</div>
80
+
81
+  
82
+
83
+  
84
+
85
+  </body>
86
+</html>
</
0 87
new file mode 100644
... ...
@@ -0,0 +1,1289 @@
1
+<!DOCTYPE html>
2
+<!-- Generated by pkgdown: do not edit by hand --><html lang="en">
3
+<head>
4
+<meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
5
+<meta charset="utf-8">
6
+<meta http-equiv="X-UA-Compatible" content="IE=edge">
7
+<meta name="viewport" content="width=device-width, initial-scale=1, shrink-to-fit=no">
8
+<meta name="description" content="ClassifyR">
9
+<title>An Introduction to **ClassifyR** • ClassifyR</title>
10
+<script src="../deps/jquery-3.6.0/jquery-3.6.0.min.js"></script><meta name="viewport" content="width=device-width, initial-scale=1, shrink-to-fit=no">
11
+<link href="../deps/bootstrap-5.1.3/bootstrap.min.css" rel="stylesheet">
12
+<script src="../deps/bootstrap-5.1.3/bootstrap.bundle.min.js"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous">
13
+<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous">
14
+<!-- bootstrap-toc --><script src="https://cdn.rawgit.com/afeld/bootstrap-toc/v1.0.1/dist/bootstrap-toc.min.js"></script><!-- headroom.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script><!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script><!-- search --><script src="https://cdnjs.cloudflare.com/ajax/libs/fuse.js/6.4.6/fuse.js" integrity="sha512-zv6Ywkjyktsohkbp9bb45V6tEMoWhzFzXis+LrMehmJZZSys19Yxf1dopHx7WzIKxr5tK2dVcYmaCk2uqdjF4A==" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/autocomplete.js/0.38.0/autocomplete.jquery.min.js" integrity="sha512-GU9ayf+66Xx2TmpxqJpliWbT5PiGYxpaG8rfnBEk1LL8l1KGkRShhngwdXK1UgqhAzWpZHSiYPc09/NwDQIGyg==" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mark.js/8.11.1/mark.min.js" integrity="sha512-5CYOlHXGh6QpOFA/TeTylKLWfB3ftPsde7AnmhuitiTX4K5SqCLBeKro6sPS8ilsz1Q4NRx3v8Ko2IBiszzdww==" crossorigin="anonymous"></script><!-- pkgdown --><script src="../pkgdown.js"></script><meta property="og:title" content="An Introduction to **ClassifyR**">
15
+<meta property="og:description" content="ClassifyR">
16
+<!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]>
17
+<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script>
18
+<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script>
19
+<![endif]-->
20
+</head>
21
+<body>
22
+    <a href="#main" class="visually-hidden-focusable">Skip to contents</a>
23
+    
24
+
25
+    <nav class="navbar fixed-top navbar-dark navbar-expand-lg bg-dark"><div class="container">
26
+    
27
+    <a class="navbar-brand me-2" href="../index.html">ClassifyR</a>
28
+
29
+    <small class="nav-text text-muted me-auto" data-bs-toggle="tooltip" data-bs-placement="bottom" title="">3.3.2</small>
30
+
31
+    
32
+    <button class="navbar-toggler" type="button" data-bs-toggle="collapse" data-bs-target="#navbar" aria-controls="navbar" aria-expanded="false" aria-label="Toggle navigation">
33
+      <span class="navbar-toggler-icon"></span>
34
+    </button>
35
+
36
+    <div id="navbar" class="collapse navbar-collapse ms-3">
37
+      <ul class="navbar-nav me-auto">
38
+<li class="active nav-item">
39
+  <a class="nav-link" href="../articles/ClassifyR.html">Get started</a>
40
+</li>
41
+<li class="nav-item">
42
+  <a class="nav-link" href="../reference/index.html">Reference</a>
43
+</li>
44
+<li class="nav-item">
45
+  <a class="nav-link" href="../articles/index.html">Articles</a>
46
+</li>
47
+      </ul>
48
+<form class="form-inline my-2 my-lg-0" role="search">
49
+        <input type="search" class="form-control me-sm-2" aria-label="Toggle navigation" name="search-input" data-search-index="../search.json" id="search-input" placeholder="Search for" autocomplete="off">
50
+</form>
51
+
52
+      <ul class="navbar-nav"></ul>
53
+</div>
54
+
55
+    
56
+  </div>
57
+</nav><div class="container template-article">
58
+
59
+
60
+
61
+
62
+<div class="row">
63
+  <main id="main" class="col-md-9"><div class="page-header">
64
+      <img src="" class="logo" alt=""><h1>An Introduction to ClassifyR</h1>
65
+                        <h4 data-toc-skip class="author">Dario Strbenac,
66
+Ellis Patrick, Graham Mann, Jean Yang, John Ormerod <br> The University
67
+of Sydney, Australia.</h4>
68
+            
69
+      
70
+      
71
+      <div class="d-none name"><code>ClassifyR.Rmd</code></div>
72
+    </div>
73
+
74
+    
75
+    
76
+<div class="section level2">
77
+<h2 id="installation">Installation<a class="anchor" aria-label="anchor" href="#installation"></a>
78
+</h2>
79
+<p>Typically, each feature selection method or classifier originates
80
+from a different R package, which <strong>ClassifyR</strong> provides a
81
+wrapper around. By default, only high-performance t-test/F-test and
82
+random forest are installed. If you intend to compare between numerous
83
+different modelling methods, you should install all suggested packages
84
+at once by using the command
85
+<code>BiocManager::install("ClassifyR", dependencies = TRUE)</code>.
86
+This will take a few minutes, particularly on Linux, because each
87
+package will be compiled from source code.</p>
88
+</div>
89
+<div class="section level2">
90
+<h2 id="overview">Overview<a class="anchor" aria-label="anchor" href="#overview"></a>
91
+</h2>
92
+<p><strong>ClassifyR</strong> provides a structured pipeline for
93
+cross-validated classification. Classification is viewed in terms of
94
+four stages, data transformation, feature selection, classifier
95
+training, and prediction. The driver functions <em>crossValidate</em>
96
+and <em>runTests</em> implements varieties of cross-validation. They
97
+are:</p>
98
+<ul>
99
+<li>Permutation of the order of samples followed by k-fold
100
+cross-validation (runTests only)</li>
101
+<li>Repeated x% test set cross-validation</li>
102
+<li>leave-k-out cross-validation</li>
103
+</ul>
104
+<p>Driver functions can use parallel processing capabilities in R to
105
+speed up cross-validations when many CPUs are available. The output of
106
+the driver functions is a <em>ClassifyResult</em> object which can be
107
+directly used by the performance evaluation functions. The process of
108
+classification is summarised by a flowchart.</p>
109
+<img src="data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAvIAAAFPCAIAAACgRb0tAAAAAXNSR0IArs4c6QAAAARnQU1BAACxjwv8YQUAAAAJcEhZcwAADsMAAA7DAcdvqGQAAHIPSURBVHhe7Z35e1XV9f/5Byr480cRse3TWurYVkFkEEVbtVa/Cm3V1rGArYozKE5VEe1jbZ2oE0VFHKAqgiMggyAghDGMSTPPhgwmIQPVfl+567B7cocQcs9Jcg/v15PnPuess/bea+999l7ve+690O+/QgghhBCRQLJGCCGEEBFBskYIIYQQEUGyRgghhBARQbJGCCGEEBFBskYIIYQQEUGyRgghhBARQbJGCCGEEBFBskYIIYQQEUGyRgghhBARQbJGCCGEEBFBskYIIYQQEUGyRgghhBARQbJGCCGEEBFBsiZIvhVCZCDeAhZCZD6SNcHAzvjNN99UXffzstGD9Kc//WXQH8uWxStxI0Q0kKwJANM0ra2tbJFff/11fX19XQwOhBB9EP8KZdmyeKVshIgGkjUBwG7Y1tbW0NDA/lhRUVFeXs6rEKKPw1IFli2LlyUsWSNEBJCsCQDe57W0tNTU1LA/FhUVlZaWStkI0cdhkbJUWbAsWxYvS5iF7C1pIUTGIlkTAOyG+/bt++qrr9gfS0pKqqqqamtr9SGUEH0WlieLlKXKgmXZsnhZwpI1QkQAyZoA8Msa3gWyaTY3N7cKIfowLFKWKgtWskaIKCFZEwB+WcP7v6ampv3792P8VgjRJ2F5skhZqixYyRohooRkTQD4ZY3tj//5z3/YOr3LQog+BsuTRRq3bCVrhIgAkjUBkChrtD8K0cfRshUikkjWBID2RyEyDi1bISKJZE0AaH8UIuPQshUikkjWBID2RyEyDi1bISKJZE0AaH8UIuPQshUikkjWBID2RyEyDi1bISKJZE0AaH8UIuPQshUikkjWBID2RyEyDi1bISKJZE0AaH88nKmurh4/fny/GDNmzPCsos+jZStEJJGsCYAI7I/ffvutJWbHcccdN27cuLlz59Ijz6n3SAzPz8qVK3vr33Sm3bFjx3px9Ov36KOPMvW9FYw4JCRrhIgkkjUBkOn7I2n4P//5j5eZEzjyyCMXLVrUi6m68/Dgs88+6xUxQYt79uyxGFavXl1fX9/U1NTW1tb3Z5/ICXLq1KlE/pOf/KQvKNeeJ9OXrRAiKcHImn//+9+2uRuPPfaYd6EL4Pz555/b8bnnnjtp0iQ7DhZqBu8kaDJ6fzTRQMw2d++8805xcXFpaenSpUtfeOGFk08+2ewLFy7shm5gzCmbzkczLrza2tqKigpimz9/PnWOHDmyqKiopKSkqqoKPdHa2trzY06LKCqCGTVqVGFhIbEx+/YfnXZjrMKGWSBUZsQ0DSN25513Yjn11FMrKyv7YMBhc9Bly5gchsMiRKYTgKxBl7A5vvHGG945lcZ2T++kUyiFM6rIOw+N44477pDE1iFx0P2xL8PGTYarqalhImD27Nlbt27Nzs7euXPnnj178vPzf//732MfMGAAqqLru3wsI3gf0KTz0Qyl2traEC4oLeIhtlmzZlHn0KFDN23atH379ry8PPtf01E/3Wuie1hgn3zyCcEMHz5827Ztu3btQmYRKvaejOSgEAwwC4TKjDBQzPjXX3/NvcrQoRebm5t7ePT6AqmWLePAAQPS8NE8/rp96woheoV0ZY1pmkRdgrErMgIfBId3Ehr2MMk9EwqcVPtjRkCoZDXerzNE8MILL2RlZW3evHnLli1oCMvWI0eO5BJv7rue/KiW7H722WdT8OGHH7anKd1IDxRxsmb37t1ImZkzZ1Lnz372s3Xr1hEhk9srsobutLS0LFq0iGCGDRtGYIRXVlaGXOhrssbmglkgVGaE6W5sbGTQCgoKGL2+GXMPwLDELVtuIYz79++v/+CtiitGlY39/t6Xn2BkunfrCiF6hXRlDRul/zmNw69XOD733HNNAIH7mMk+oTDYXuOe3Piv+hWJ1WxKBeJUEadmB1dV2M+EEvdHLN61Po8FX15eboM2a9asnTt35sZA0CBr0DevvvoqlwYMGEBGdFs8iXz8+PG8+4cZM2bQcfuYg1d8li9fHqvvf0yfPt3KAmrACsLcuXOx2HSvXLnSonJwiWRDhDU1NSUlJUiHl156Cc/TTjsNTZOXl1dRUYHoOeecczDSNFHZPUD8rgbs1ta4cePs+8U4AAeAhWMCoCwOHB955JF33303PbIagBqsWhyomVJE1V5FR+6//37LjjYaVoTaGCgq9+qKhWT9jQsYOxazc0rAHPNKbVxi0FwM/tiAU5ZVrItjJ06cSFnXKcacPM2xnzFjxjDj9iEUmtX/hImC7oddP/nJT4jE7IabJtc7fGxIPY/Mwe58ho5li8hD6iG+6xa9WX75SASN/VX8YwaaDztzGiA0DZk4aEL0fdKSNSYXvJOO+C/ZVogc4djkiFNC/mO/EuLAHceJEmrzX+XAarZjp5lMRblj5x8G/v2RV46xeNf6PBY8b9kZLpgzZw7qgV5UV1eT+fLz83fs2IGysasc2JtXtIhZHIMHD54wYQIHyBfSwJIlS8zuePjhhynLnk7e9UwHQJSYLlmxYkXiXo+FUigqsi9xEiGeQ4cOJXkTZ0NDA5es+F133UUYHPBqyYN0deqpp2LxQ4R2QL7HbdmyZRxTBP1hdoM4qYHW4zqLW1ZWFn30zn08+OCDLS0tKK3ERsEEnHUH/YHFH7AFYx8VEaG/BgZ2w4YN/vAobrEBwiguck6pmQOGhTiZX7M7zjrrLIKcMmUKx6NHj2YMaZ2qEqcViIRh5CotWtiJvduzZw8O3oRlCHTHlm3JqEHc6tXvzfELmh74aykpYMa9aIQQAZGWrEFDIDK8k474ZQ0H/i8Cu1ImcfzfFza7X5EYfr3CJXMz3CV/i0C1nJoYwt8fQOC4/TECT2vefPNNBE1TUxNagde9e/cWFhZmZ2fb1YULF2J3P/+5+OKL169fX1lZSdLl2IwPPPAA+qOmpqaoqOiMM87AMnnyZCbCqrUHP3Dfffft2rWL4frwww/dF5MXL15s+dUL7gBYSAAoBuKxiR42bBj10xDxEP+YMWMwDhgw4IknnqBp7BhRUaa0sD///PPESXMvvfQSp+2N9etHOiekTz/91E5POukkOkIKv+qqq8xCDcTjJBc10Jdrr72WgryJRxm8/vrrXDrttNM2b96MBKSPvOk/5ZRTMNKp999/n4Glm/fff397df36LV++nAqJOTFgG/OHHnoI+7HHHoudaE1yAbW9/fbbdN8pD0aDMWH6TBjhwOwQ4e7du5kC86EVNxe33HILFsYNOYg6JLC7774bC7KGsaIqiscKtc8gMeNA/IwJFkaAoaBF+1QRXHg2mKZZM0vZ2J3PiBWPHlT22xFxmqMH/kr/eu/eWU8mveGFEN0mLVnTiVxw0iROu4CTNXFCxD13cQcO15CJFX9tnJqze5xj+LVRYoXBEiVZQ+4kC7qn7lwizefk5NjVL774goz+hz/8geOLLrooLy+PJEoKxIGkfsEFF2CfOnUqWdO+CnP66adjueGGG7Zt21ZcXExWJmFjIQv6C27cuHHgwIHYP/jgA1J70tFj6ycqYkN44Ul6LikpQVvgX1dXN2rUKIyXX345t0FBQQHdwUijGIFq/c0hpMxOSkOILFiwwE7RHKR8RJvTbaZ7LrnkEo65A9euXYsDHWFMgIbs+8s//elPubRjxw4uWXiDBg3Kysqi0Z07d9IupW688Ubsl156aaqA6Rr2e++9F/uZZ55JqIRBDcOHD8fypz/9CX2Js4vt448/piqTia4518dHHnkE+8iRI91cUAMW+/COeqjNnugga+gjosSewTz++OMUd5EjXPr374+dqUch4cyxhW1jdccdd2BBpFIJN0wGZWhuM2Jm5P894pjdq1fk3zMhTnaE/bdj9Hfzzv4eSyyzxk2IPk5YsoZLwEGcdgEna5AaCA4zskvihl5xB2Y38LeG/GIF/CrHLvmxypNWGCwRkzW1tbX2zhs4INfOmzePS0cccQS5kKv2pGHu3LlbtmzZtGkTaXL79u0k9eeeew77rbfeitwhVWMhiWKZOHGiPcxwrcQVRH9cd9112N99912URNJd3oKh9bfeegvPM844w2QNmQmFgQ7AePPNN1MVudYklMkXZEFic8cffzyXCJJKrEIsOGRnZ/OKMxagZtTGkiVL6LtZaBeRZE87uLVefvlljMia1atXUy19tEcgEyZMoB56bXBsn50NGDCA8ayoqEgMGIEF9m/J3HTTTcRgYQ8dOhTLK6+8QvCER22cwnvvvYfOePDBBzlGW8T10ZYG0bq5QFxi+dnPfoaIpEXUz+23344FgWXqkGP48ssv4yI3XfWXv/wFFThixAiOn376aew2VnQBCwqJAW9pacmsO7+xsZGp3H3mQHpKx1e9N3/bzZf7lce6qZMWLVr0ySefLA6OTz/9FEm6dNgxG0cOzh3z3YwbNyH6OGnJGr8u8WNKAkHDcaKPe3bixArYLkxBKxunQlxt7VrJ9wmUUzlW3F/KVW66imrNHgamDCIpa/bv30/Os19CTZ48mbRNB+0t+zPPPJOVlWVZmeHlFQt28hwps6ioCIul5D/+8Y+kVSwkb07hs88+8xckJV999dXY58+fT3OpPodKKmuQQQRvn3bdeOON5FqCJAEjR95//32M6JW4OGnuhz/8IZeIk5RvguP0008nSXN1165dJDksQMBUhQ+3FnrFxFD//v13797NOHAVtYEFrbBhwwaMyD77wgoqjdrsR/JUSOuzZ8+2skglCiYGjNyhTvsaLyOG+ECgUNDG8MUXX8TTquIU0JpUZU93aC6ujytWrMBOWTcXSCUsdJNq0Tq5ubn2sRSTy6gykhzDypUr4yIfNmwY9kceeYTemcR54YUX3FhxV2BByzILGXfno4mRNXtGDKSbDCB9/+ijjxbNfmnTH8ebrFl/zx/RNNyuy5cvZ0jTZ9myZahkBPeKMwZtHjn432O+x22cWeMmRB8nLVnDBsqOFidBAOHixAcHflnjFxlO34BTP1aniRjDaRfgwBWBdo2T7JmQVWKerubwMGUQSVnDwbXXXov9iCOOYFO2BHzllVdiGTt2LLnNLPS6tLT0F7/4BXZkDSmTbEE2teRN5iOPYiEvHn300VhIxv6Ca9euPeqoo7CTquvr6w9V1lCzNUTTTD3JnkpQCV988QVGoFp/c++9957ZSczY3XeQOaVONAdJ3RwQNBUVFYSNpCDtoYf+/Oc/Y//rX/9KE9RmHzmhFdBtFKRye35DN3n3T20EY891rr/+euznn38+Rqo1reACtk+7eONusga5Q4W4cdU8qZbwiISx5RS452nu6aef5pjRIyX7+2hPcdw3aZgLlIdZqBMHnE3WjBgxgnZRgSeccAKnTI2Ng0VOOrcnVQwaCsnG+aWXXnJjZY98qIrjxsbG/2TOd2BN1jC/BSOPYZSAWV63bh0iZtGiRR+99s9tN1++9c+32uMrpgO4MdKEJhCsTNbGkYN3nfXdwrO/x0TYE0ovLCFEeqQla8A0h1Mh7JicmtQwOJ00aZJz4NTUhnk6uxMogL8TIqZXzC3xkYyrLe4Sx2ClqNY9EwqJ6Mma1tZWNt/nnnvOvo7av39/xATvaMmOJE42ZXNGx5AG2JTZrN1Xhu2hDm7UaW/uSajkPCzkabthgPRJkiav8M7VEiqkKWtuu+02GsXS3NzMJaK1H2yTmP/xj3+YdCAl25dFwC9ryPfEQ4JnBslw5kDAnE6bNm3gwIHz589H1vz617/G/sILL1A/wdg/eWzqgQQJHPzoRz/CSKd460+LlLInJYA4oBUaNbHiAmbAW1pa0Bb2fRcTgowY+sPG8JVXXqEgFkayvaLYh4B0kHVkSnHIkCELFiygKhzcV4Zpxc2FfQmGgcIByUJtTtZUV1fTTRNkMHXqVKolcqZj0KBBWFhE9qzIxtmCsbEyHUbABEPrmSVruPMZiuJRgxhnRqld4hQUbN++HSnDZrJ69epNmzYxFIwePbVPCdPERn7z5s17zvpuwdnfKz7n+9TPvSRZI0RQpCtrwASKwykVsEtsEAiLxKvslVhMc/if3IDzByoxo2VEOwaTMnFXDbtkbXHgrzkMoiRrEjnmmGNI3uzvu3fvtv2dfdk/2sbJJ59sX0olWZJKcSNJ2DdIeENP2mBDJ2eQ4y+99NJYif9x5ZVXWr6koXRkDSmWzIE+wBM7iXbFihX2yZEfe8IBfllDDdRD62gLJIU5EDCn9pzDgUji7Tt2gnnnnXewoB4oQpfpIzckss+UTRwMGu/XGT0ajQuYrIayoUKTNfbwA91ArrUxfO211+gvFoJsrysma6gKFYUSdV/9MQYMGGA/YjdZY3Nh+gORxFxgYXCsX8gaF/njjz/eXr4jCCaGEVHrZA3BuLFyOixDZQ19Lx09iHHmXkLJ8WrKg3sDOGCCGhsbmSMmKH1okQpZSkXnfK/knO+XjpWsESJgApA1nYCwYMvzTqJLBGSNS5aOY4899qKLLnrqqad488qbS96ss8WTxurq6sivJLmXXnrpvPPOGzly5FlnnfXggw+yU7s37pZKXUpG1lA/KZlUTcENGzb85S9/sYJjxox5/vnnyc0kYDy7/bTGHmmQYomQ5EENpCjyN80tXbqU/G3NXXLJJQsXLnQPY0zW2I+0qYHcT4U0gdEc6DKnhHTffffZMx60+AcffEANJD/acrKGInQQUEKMFcKaYOxRB1xwwQX/+te/kHS0yCDgY/rABcwsWO9MJRAwwXNKKzaGBEk3cXYClMVFVbSLxlqwYMH48eOtj9dee+369evd78XcXDhZQz1kVr+s8Uf+yiuvnH/++e0NxH5gNWXKFIzcADt27CB4Cxsh6MbKvkuU0bLGli03DLcNNDc30xGGmjHhbscHI87cgelDVdxO3D8IGvv6jmSNEMESrubwf5wUYeL2x0yUNSRLshfpcNOmTbwpZ6tl5+WAlElKQxzk5eWRC9n6gVxLhtsYAx/SoeVXV4NLpVRCWRQPWZAUiIXjVAVpCMtBZQ2RoA8oQuI3WUPw1EZDVIUDbiQJkhMxdBInRq5iJCQLkvCojRow0gR9R9aQ20xMUHDnzp0ECRTEGTsV2hd7nQDCk6oswpycHKJlEJw0pGaGglKoBH/AzAKvJFEs2GkI8WFfImYuLDxqxtnqx0Ll+DAIdC1VH5POBTXQqUOKHDeObawYFl4Tx4oKM1rW2LLlNuOVXsSerbTavZR4N3YbauOmZU5N00jWCBE44cqaHvheS18g6f7oXevzECoKgCxFKiURrlu3zr4ba5CusJO66BeChl2evZ4UaEmRVGrZmoSKG872exzeuJPykUEU5BIbN8XJeeTpzgu61JhK1tA0aRhNQGZFHzQ2NprMIulSFcVxcCqBbNFJc7wSGA68uiCp0Hpn3w/lAAVgn0rgQxGEAnGiFegd3UEKIHG4VBL7Ty6ZejI93acso0ej9gqUogkTQ5RCNyQGbE1j5yqenNK6NU1ZwsDCqwVsk2LPXQ5pLiwGJFHXI2d48SdstI5VkjhWODAXGZSeO1m23GzAKXBgxkCQrBEibKL/CVEPwN6Xan/s+7Bro1TIc6Q9kqJJGQ5IVKQ90hjpiqt0yh7FQ0tLCymQfIa2IKECB2RioAgpn8TJTk3OQ3mQKakBBYB4gs4LkrNpKOkWT5zYSZxUTqa3bO3qLC0txUJxy6yWkzqPsz21lJVRhFd/kKaTGA1a4QCjPdugCPkbKGgfweBplyhu8440oQYCM3+GEU0ADKb1DtFGKRwQE3EBW++wYOcqPpzSihtD+oKS4NUCxs4IY7HmUg1p4lxQA2EcUuRUwjhQMG5CLWAGClBOWBh2b8L6PIRKx3t42TLLTIdkjRDhIVkTAL2yPwaFJVRiJs+RrshqQFrlrTkZy1KgfacVT+ePhUyJA3oCZwqS+eg7UI8VIcmxX1MDnhyjirpSkPxqDSXCqKLA8CH7Ui05FWcgeEu6XMLBBr/zOLHQHJcowqsLktpcE8ABRpMODIjVQHFrCIjBmsaHsjRNoxSxRvFHBDCelKWGTgImWtc77FzFh1Pid2NoFl4tYOxcpTbXXBfnghqwHGrkcZVwTCkLGAeM+CT99LDPQpcZCkZJskaIKCFZEwC9sj8GiFMAZCaSHHBAL0hd5C0u0R1/urIcbAkVZxKb8wfLtZQCy3x2SqmDFrQHQrh5LXXEFceTat3TIyrn1Bri1BU/aHNcMqws9cTq+18TZqQhTilLDdRDWezmyaVYy14wtJjYKNAoPq7+pAG7gnbJnHk1C6+pLMCxa64rc0GRbkSeWIn5+6fDRj4jIFp6J1kjRMSQrAmAXtkfg8VSGrC9gh2DZTvPqSNWxPzB/A0rFYcrBfh4xRIKmlsqXHE78BsdZnRgwd9r7GBxmj/EXeXUKx+rAYur3GEWg9PEIs7Hjh1mBO/8UHCl4ppz2NXOsdYNTinlVdQxcjtwOIvfJ4MgbMkaIaKHZE0A9Mr+2Hfodj7r4USYfnPtqfsQK+lGkXQIsK0ejrznkawRIpJI1gTAYS5rhMhEJGuEiCSSNQEgWSNExiFZI0QkkawJAMkaITIOyRohIolkTQBI1giRcUjWCBFJJGsCQLJGiIxDskaISCJZEwCSNUJkHJI1QkQSyZoAkKwRIuOQrBEikkjWBEDi/sgmFe1/80OIjIblySKVrBEiekjWBIBf1lTF/vNC/z9ILyIAs2l45yLDYSpZpCxVFqxkjRBRQrImANgNPVlz/hC2SP1F6a909KCSUYNKRh9bctbg9r9R7ZY4H/1l9t/5QyRrhIgMkjUB4GSN/d/XvP+rjf0nzPUiw7H/47pdsP52hCWhqh1ba2pqNLmZjs2s/V/lLFvJGiEig2RNALAbtrS0kO3YIouKikpLS8vLyytE5sM8kvNycnKKx59hSShnzedMcVlZmechMhYml6XKbLJsWbzNzc2SNUJEAMmaAPj222/b2toaGhp4z8deCd7GKTIc5EthYWF2dnbRuGGWhLYtW5yXlyflGg1stbJsERYsYRayt6RDQ7JGiLCRrAkA+wZia2trY2Oje8StzykiAG/iSXs7d+50siZ7+RLe3O/du1fzm9HYCgWOWbYtLS0IC8kaISKAZE0wuN9W8J4PfSOiwb59+1A2OTk5hZcNtSS0a9XyyspKS4Sek8hkWLDud4veYg4TyRohwkayJkjYGUWUIOGRcvLy8tzTmpw1nyN0SIeWCEVk8NZwyEjWCBE2kjVCpIRk09DQkJ+f72RN7tpVtbW1PfM9DBE9JGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSIlkjgkWyRoiwkawRIiWSNSJYJGuECBvJGiFSkihrctZ8Llkjuo1kjRBhI1kjRHIQLvv37yfl5OXlOVmz54uVNTU1ra2t33zzjecnRJeRrBEibCRrhEgCmoZM89W9E1z68f+Vjxva1tSoBzbiUJGsESJsJGuEiMc0TXNzc/XGtS79+P8qX3uWq/hI2YhDQrJGiLCRrBEiHvv4qaGhoaSkpODWK1wGsr/iS35a9O/c+vp6fcNGHCqSNUKEjWSNEPGYrEG4FBQUbFowz2Ug+9v+5IOkIn1xWHQDyRohwkayRoh4ECukmYaGhqKiovXr1++c9P9cEir81anrVn2O3CEVIX0ka8QhIVkjRNhI1giRhG+++aa5ubmqqio7O3vV3NkuCWU9OnXLli3l5eX79u3Tj6HEoSJZI0TYSNYIkYRvv/22ra2tvr4+Pz9/zZo1OyZeQgYq/NWpq5cvy83N1SdQontI1ggRNpI1QiTHHthUVlZmZ2d/8earZKBNj91jj2qampqUh0Q3kKwRImwka4RIjntgU1BQkJWVtfvuCRvWfJGXl6dHNaLbSNYIETaSNUKkxB7YfPXVV7m5udu3b8/JyamsrNy3b5+SkOgekjVChI1kTZDwDl5ECWRNW1tbQ0NDVVVVaWkpmoYMZP9zguchIoG3gMNHskaIsJGsCQZ2RlJd1XU/Lxs9SH/6018G/bFsTad6izlMJGuECBvJmgAwTcObeLZIdqj6+vq6GByICFBbW1tTU7N3715eOfasIpPxr1CWrXsC5y3p0JCsESJsJGsCgN3QPqpgf6yoqCgvL+dVRAnm1PDORSSwOWXZsnh75mvgkjVChI1kTQDwPq+lpYW38uyPRUVFpaWlyn9C9HFYpCxVFizLlsXLEmYhe0s6NCRrhAgbyZoAYDfct2/fV199xf5YUlJSVVVVW1urD6GE6LOwPFmkLFUWLMuWxdsz/2y0ZI0QYSNZEwB+WcO7QDbN5ubmViFEH4ZFylJlwUrWCBElJGsCwC9reP/X1NS0f/9+jN8KIfokLE8WKUuVBStZI0SUkKwJAL+ssf2RTYqt07sshOhjsDxZpHHLVrJGiAggWRMAibKmB/ZHIUQ69MqylawRImwkawJAskaIjEOyRohIIlkTAJI1QmQckjVCRBLJmgCQrBEi45CsESKSSNYEgGSNEBmHZI0QkUSyJgAka4TIOCRrhIgkkjUBIFkjRMYhWSNEJJGsCQDJGiEyDskaISKJZE0ASNYcJsT+fdr/4Vm7zGOPPdavX79zzz23G2VF4EjWCBFJJGsC4HCTNStXriQ9J4VLkczZdGrRokVjx461bg4ePHjChAkrVqxoVzdd6y9uM2bMoCyVkMO6WKobxCJqxzsXKZCsESKSSNYEwGEla+ja8uXLLbsnsmzZMhwillPpzuuvv+71sCNz5szpSn9xwG369OkUOfvss5ubm/fv3x/4KFHh1KlTaeLUU0+tqqoKvP6IwYxI1ggRPSRrAqBX9sdegUxJPl68eHEsp/crOkBxcXFpaSl9b2hoaG1tDbb79pCjtz67odE9e/ZYfx977LGNGzfm5uYi7K688sqrrroqPz/f+tt5bFxta2t76KGHqGT06NG1tbUom4OWOij+kQFS41133YXllFNOYTrCUE5RoleWrWSNEGEjWRMAvbI/9gr0i3y8aNGi9iTfr9/mzZu3bNmydevWbdu27dy5s6CgoLq6mu6zRweSUKmEFh999FHaGjt2LMc9n6dpdOnSpQQwYsSI7du30+VNmzbxmp2djb6pqKhAyR1UQFBJS0vL/fffb/WUlZV1pVQnxI0MAw4IrPr6+srKyvLy8r179wY4EZGEAez5ZcuMSNYIESrByBpWJturgze13oUugPPnn39ux7zvnDRpkh0HCzWDdxI0vbI/9gpsvk1NTe+8845N9Lp16zZu3IiyCUPWWOYmVdtDjrPPPhtl0MN5mrYQH6tXryaAI444Yu7cuRs2bEDToOSQNbt37y4pKUFJtLW1dR6V3SH33nsv9QwfPrywsLCuru6gpVKRdGSojampqqrKz89Hb5WWlpIsu93E4UCvLFvJGiHCJgBZY7/veOONN7xzKo09GPdOOoVSOLOwvfPQOO644w5JbB0SvbI/9gpsvg0NDf/617+YNSDB79mzhzxaVFREgienskG7D2VWrlw5btw48/zJT36CJkhMsQwXQnZsjIkTJ+bk5Nj3kbl/qISsbMUd55xzDjHYsauNA/yx2BeWwRw4pdEjjzyS2cdozqR8GsKIA/YZM2YQg11KhFJ0p6am5swzz7Q6x48fv2zZMnQJFBcX0+XGxkZ77gI0R0/Nk7677xTbHTJt2jTsZ5xxBiNWW1trmuOg8eBjI2k+BjF4RwdA3BCJKSei9eutuCY4dk1w1T7J4nXRokUWPD4zZ87kkvlElV5ZtpI1QoRNurLGNE2iLsHYFRmBD3uodxIahEc87plQ4PTK/tgrxMmaRD777DN86D4J3jP5mDBhApcsX/K6ceNGf6oGTu3bIcgX9ERTU5PZHWPGjGlubrZjqwpoEVWEBRmBkVNzeOaZZ+yAdlEeXEpsETr5gi1Gwqiurv7yyy+HDh3qFejX7+qrr6aquro6lISTccgF77KPOXPmEA/QF5M1w4YNy8vLQ9ZQsPN4jKTfVv7000+9owMwMkyNfc41cuRIp7eSNoEFO2GDfZJFo3bJYd+G9gYiitA7yRohoke6sobtz/+cxuHXKxzzZtoEELiPmewdtsHajnty47/qVyRWsykViFNFnJodXFVhPxPqlf2xV2DzJXfOnz/fRjiRpUuXtrW1ue/YkmV37txZVla2YMGCk046Ccurr75KJYwPDB48GAt2rpaXl+/atcuyMpCk6+vr9+7dW1BQMHnyZCyoipycHPvWiPnYZ1JkbgYcfyxLlizByKk5HHvssYsWLUKUoD9QFcgIa/Hiiy9et24dUa1du/ZXv/oVlj/84Q9UhYbw+nkALHQHCcLNgw545JFHjjjiiFjd7cyePZs6rTsmPgYMGPDiiy9WVFRQ+cyZMznFuGPHDtziZE1NTQ36rPN4qNaN5FVXXcXV0tJSRsC+PUNIbmQ45sZjxB544AEso0aNsu/W7N692zRNYhPERiUMl32SBWg1/JmvE088kdOzzz6bvhODNxaRg671/LJlWiVrhAiVtGSNyQXvpCP+SyZQkCMcs4Y5dkrIf+xXQhy44zhRQm3+qxxYzXbsNJOpKHfs/MOgV/bHXoHN1y9rsrKyyIK5ubn5+fmFhYWkcwQE3b/++uu5euONN3IJh+zsbFK7ffEWqYED+RJ9w+mgQYM2bNiAD5DCmeWHH34Y+8iRI8nBJSUl2P/4xz9iOe2007Zs2YKyoS1OgWRAVkYcIDtI5Fg++OADwuPUHP72t79ZbFSFcdasWRhPOOEEf1Q0eswxx2DnmN7FKRtOrcvUgAP9XbZsGZojVn077777LroKHxMor732mr/yJ598EuM111zT2NhItE7W0E1kR+fxbN++nd7dcccdHF944YXYuYoRTwaB061bt95www1cZWQoy1gh4O677z4s9rSGsK34L3/5S2uC4lRCcRrFzvighOxzq4EDB+LDJcTlnDlzsIwePdp9vuYNR7SQrBEikqQla9AQiAzvpCN+WcOB/4vArhTrmUv+7wub3a9IDL9e4ZK5Ge6Sv0WgWk5pgmP8/QEEzmEra1avXo0ocV8ZRkCQTcmUZ511ljkkZePGjU1NTQ8++CDHt99+u/22iCRNxqUSm7gzzjgjLy+voKAAo8man/3sZxQ0n/Za+vWzBxKkXuSUffflvffeq6mp4dQc0A3ke1K1P+Wn4uWXX0ZGJE4cltbWVuRacXExTRMtYcybN2/IkCGUQqXRF/e5WFKQKbSOrrrnnns4NVnDQHUez4svvshIoi04Ri0xyMAoIU1QHkAk3NVcRdYw/vZFH2ti+PDhdJmhsIl4/vnnKYu/wfFtt92G/aKLLmKs7FO/a6+91irn1fTWiBEjGGH6LlkTIJI1QoRNWrKmE7ngpEmcdgGKmC6JEyLuuYs7cLiGLOf5a+PUnE3BOPzaKLHCYOmV/bFXiJM1a9euJU0iHcj3e/bsKSoqovtkU3t2kop33nmHfGkPCcimqASyKdOHiMnNzbWvDA8dOpRjUjWvN998M5bTTz8dN1rhtb2Wfv0qKyvtKQgpHBmE5V//+hcBcGoOL730EoFZVLRoKT8V06ZNozY6GJfFKfv666+fcsop9LSsrIw4CYDjhQsXWkGTLHacCkKinrvvvptjZA1Ki6rsNBVTp04tLy9HW3D8zDPPmD6zp2L0iNfdu3ffdNNNXGWsGBYECn20Ou1byVhGjhxpxRErKCEGE0+qsk+vLrjgAsYcZcnxjTfeiDaiCaqdPXs2FrQRNUT4ZpasESKShCVruAQcxGkXcLIGqYHgMCNrGzf0ijswu4G/NeQXK+BXOXbJj1WetMJgOWxlDckyLy+PnG1f+CCt2hdirrjiCq7OnDkT3YNqwQ0dsH79+nXr1m3ZsoWMi//TTz+Nz1FHHbVq1SryNOIAPYTdnuLYIw3SKpXbowUsZGXSMOmZU1i6dCnB0CLFjz76aCzz5s2rqqpCDJnDK6+8QvonHtIGlVuLN9xwQ9Ko8KSqxM9cOOVGouCll15KPcRJ/YiDFStWxBrpR0E0ysCBA4844oiPPvooVZfpi/0TwHTEJODf/vY3TpPGw4GJmN/85jf4nHfeeRzTtbq6OoLklU4xMrfeeqtVSG1IK+xOOZkotE+pWD4mpAieaWLKfvSjH2F/4IEHsFslKCTzoVr7nhDaiNOmpibJmgCRrBEibNKSNX5d4seUBIKG40QfTjFy4MQKmEChoJWNUyGuNoqAGcGpHL++MVzlpquo1uxhcLjJGvdLKHIn/cVCl5tjcICAsP9d4Tvf+c7DDz9M+t++ffvHH388efLkoUOHrl69GmlCviS5mhYZMmTIwoULSZ8kVPvGK5CYcSCRI3TsCyJkWQQEqXr37t1MLpaLLrqIqsjlU6ZM4RRVsWnTJr+sIT2Txe1DIqLiHkBFYb/xxhs/+OADokJRzZgx4/jjj3/nnXcoRXaJkzUcM5ULFiywClE22dnZtLhkyRL7EOqyyy4jHsJ44oknOP3BD37w5JNPomOonFEizmuvvZZjIvfLGivCa6p4EI6MLQEzbjjA73//eyppaWlpbW3ltbGxkZ7ayAwfPpxRInhwsgblRBPEad9xvvDCC5FKDAXjb8/SaJr1gka85ZZbOOUVbcQoMaFvvfUWFgacGaFIVDOuZI0QkSQtWcOCZPuLkyCAcHHigwO/rPGLDKdvwKkfq9NEjOG0C3DgigCVW0NWrRnBKjFPV3N4HLayxp5wtLW1YafLQNKtra1FkdjPhhN56qmnyMGk5Pz8/Lffftv/wyIYMGCA/cdJJGYcGEx0yZ133omF5I3yQA/l5OQkFoTHH3+cePyy5s0339y7d69JAYsKC2LLrvq54oorKGgpPE7W0Du6/OKLL3quPtAfS5cuRY5wv6EPED3eBR/9+/f/8MMP0TTV1dVOczhZw32bNJ7LL7+cXuBD5fbvysSxePFiAnYjQ/0EmShraCLpWGFBu2zbto2w7WnNbbfdxtgymyibefPmYZGsCQMGU7JGiFBJS9aAaQ6nQkxPmNQwOJ00aZJz4NTUhnk6uxMogL8TIqZXzC3xkYyrLe4Sx2ClqNY9EwqJXtkfewU2X7+s4f09p04K8Lp//372aOxbt259+eWXzzvvPPM85phjkA4rV64kd5I4ERmkzOzs7Pfff//Xv/71yJEjzzrrrGuuuWbdunU240llDUXI39w5mzdvJiv/4he/iNXd/rwHtWRfm6UIbmYno9MQmgZp4qKixfHjx6M2cOD1ggsuIIsTVV1dXeJXhjnFiDZCMBEYzlZw0KBBRLVs2TL7LRgCIjc3d8uWLWgy+3wHTjjhhClTpmzatMl12X1lGGVGMHSEIknjoQt0nIKoE3zmz5+PPVarx0cffcRQuJHB2b5mFPchFE0wLOgqdJI1gXBkIlgpVEvkRGKf8d1+++1USA3E6WRNaWmpZE2wSNYIETbpyhpgWbIJOkxMGHaJPRRhkXgVwYHFNIf/yQ04f6ASM5qEsmMwKRN31bBL1hYH/prDoFf2x16BzZf0SdLdHoMD+5qtd/nAUJBlLR8jI+ybqkAGZbJMQCCGqqqq8CHrb9y4kfyKiEE64EAaXr9+PcIFS3V1NW4YEUA4U5bhRRDgY/+JATFwiRqAhkjMCAjcOMaO2qAte5jUeVT2IQ6e/kc1QHeam5tpFE9KUdZ+IL17925OLQYrzlBQZyddrq+vx80Cc0WoJ1URtBTdZ0zwpxW6TPBcolPoFXqKD842MvaoiVHFyGBiZPTwcU1QnAOK48xVLAxdXl4e9ZuFV8aHGgiVEeYq9VCbZE2wMJiSNUKESgCyphPsnbd3El16ZX/sFayn5EsSKnAQ11n71IYUTuolVZNNgawJCALStgkItAI+paWl5E5ytqVtjq0IpziTkmtra8nuZFnasoc3JF1SOPWQmFEVRlZWFvWTodE0VI4DCZsi1GBihQg7j4qOkNGTfl+YgpbpcaYha84OTEuR+4mTpjvvsik5AkNA4Em/oJMiREsRukwRrqL/gF7jg4P9u3xIHGpjZKiKiUCCIE24ipG+E5JrwjSZDbVpGtM9+JuysUqogVBNMFEPATNT0b6Ze3jZStYIETbhag7/x0kRplf2x16BfrW0tJDFSavAQdwHN+gAvw+pkZxqeoVjy7VkSrQCPsgFfMigOADJlRRuICOqq6vJ6+z4DCluJGAyPWOLkWN8UACmBqgcf0vtVE61JGyKUAMWEkYXo0qcNQpSnEtUTvqnCJoANYPCQCjs3r2b2ogKBxrqpPLEwOgFGqLzIq2trY2NjXQf+cKlmOxp7yyRIDgIiXGgOK+Mkn2VmCaQOxhNo/iboH6KI2gYZxteShE8VblKqIF2KYuFeqiNahOHJRrQLzrbw8tWskaIsAlX1vTA91r6Ar2yP/YKlubpIOkQODDR4F2OYT4kSDZrcieJnHf/5EjSJ2mS7L4/9t8z4UPKNB+uApmVYzI64ElKtlRNaqctdADHlEUScQkfkwhU7q8ZOKBaiuBmj2q6ElViRwwriAP6gFJIivwYxbF//o7aCBIHSFU5o5QYGKVM26WKB38i55XiNM3g4EB/8aTvjAZ2Xt3IEIC/Ca5SPxbXBJX7hwuHVMPLJSyU6mRYIkCvLFvGk4GVrBEiPKL/CVEP0Cv7Y29haZ7kB6lyHkZGAAcyJaNBFueVHOkvYj6Wd50Px+RaS/l44mA+nPLKsZXiEj5WCvw1AwecmsWKdD2qpFid1iIZCE1gOsDKWhPQeeXgAvP3hdNOioA1jb29qwdGiRqwx42MObc34Os7rzi4JsA1wSW7yqmrhFd/JVi8UYgc9JQxkawRImJI1gRAr+yPvUh7/jyAZ0oGVxkHP4lFUvmkwpUCr0AMs/ivGmbxg9Erc4BUnn7MB2cnAkwWxBU0Hz+xcp0FxrHneoBEB/CuHcCMfvzOhlmAY6/YAZyDHTicv8MskYRxyAhZ0/4jiAR66yn4GzG8EyH6JJI1AdAr+6PoFbxsH8Mzicwkg2RN3G857ZeeYf/AMxFCpV3JGtHHkawJAMkaITKOzJU10Cu/xpCsERmBZE0ASNYIkXFktKzBgt07OfD8xvB/PmX/HhiviZeAU7MDNXjWGK4IWOumaQz3T6cK0QeRrAkAyRohMo6MljX+pzX+f30UsDv5YurEFefYXTJNY8dWg1M2/hr8lZuy0dMa0ceRrAkAyRohMo7MlTUmNZzx3Bh2DHaVajlGoPgvoUjsEsQJFHSMeTofswOnpnISSwnRB5GsCQDJGiEyjgySNYn4tUXcKTgLssYviUyXoHtMu3jWGIkWczYka0QGIVkTAJI1QmQcGSRrnDQxYeF/AOMXH36sSFJZgy7BaG5x4ICbfXQFVpYDyRqRQUjWBEDi/sgmpR8AC9FnYXmySDNO1oB9xuS++9K51Ej1tMZkjWftSOIl15xkjcgIJGsCwC9rqmL/l7L7N1uFEH0QlieLlKXKgs0sWQOIDIyoEztFuziVA37xwaXE79ZwYNrI1QBOzVAVpcwIVpur39UsRJ9FsiYA/idrzh/CFqm/iP2VHviLs+svIn/nD8ksWQP2OZEdm1hxagMd43SJudklEyiuKtxcDf5LVptfM3EqWSMyCMmaAHCypri4uKSkhPd/tbW19j8HiYyGSWQqq9etrF61ZO/qpbVVlZrWaGAzy1JlwbJsM07W2OMWJ1/s1PA/nsHBHu0YcfX4L/nFSpzdTv2XXLtC9EEkawKA3bClpaWmpoYtsqioqLS0tLy8vEJkOExiWVkZOa/0N2daBira+KUmNzLYf2nOgmXZsnibm5v7pqxJB5M13okQhweSNQHw7bfftrW1NTQ08J6PvVJpLxowj2ianJyc4vFnWAbKWfM5WRCt43mIDMdWK8sWYcESZiF7Szo0JGuECBvJmgCwbyC2trY2Nja6R9z6tCLTqa2trayszM3NdbJmzxcryYK8s9fkZjq2QoFjlm1LSwvCQrJGiAggWRMM7rcVvOdD34gIsG/fPhRMXl5e0bhhTtbwzr6pqYks6DmJDIcF63636C3mMOlhWSPEYYhkTZCwM4rIQLZraGjIz893siZ37SqEDrnQsqCIEt4aDhnJGiHCRrJGiOSQaRJlTW1tbc98CUNEEskaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEiOZI0IHMkaIcJGskaI5EjWiMCRrBEibCRrhEhOoqzJWfO5ZI1IB8kaIcJGskaIJCBc9u/fT77Jy8tzsmbPFytrampaW1u/+eYbz0+IQ0GyRoiwkawRIh40DWnmq3snuNzj/ysfN7StqVEPbEQ3kKwRImwka4TogGma5ubm6o1rXe7x/1W+9ixX8ZGyEYeKZI0QYSNZI0QH7OOnhoaGkpKSgluvcOnH/oov+WnRv3Pr6+v1DRvRDSRrhAgbyRohOmCyBuFSUFCwacE8l37sb/uTD5KH9MVh0T0ka4QIG8kaITqAWCHHNDQ0FBUVrV+/fuek/+cyUOGvTl236nPkDnkI6SNZIw4VyRohwkayRoh4vvnmm+bm5qqqquzs7FVzZ7sMlPXo1C1btpSXl+/bt08/hhLdQLJGiLCRrAkM3ruLaIBkaW1traury8vL++KLL7ZPvKR07PcLfnXqqmWf5eTkuN94e94iw/EWcI8gWSNE2EjWBAA7I0mu6rqfl40epD/96S+D/li2plC9xRwykjVChI1kTbqYpuHtO1sk21N9fT3v8oEDkbkwg9XV1SUlJdnZ2StXrsy6/ZoVSxZv3bq1qKgIu+Y3o4ktUG8GWbbu2Zu3pMNEskaIsJGsSRd2w7a2toaGBvbHioqK8vJyXkUEKCsrKyws3LFjx9q1a1E2a9asQeIUFBSUlpZ6HiKTYakCy5bF22O/a5OsESJsJGvShfd5LS0tNTU17I+8lSfnSdlEA+axpKQkLy8PZbNly5bt27eTgYqLizW/EYBJZKmyYFm2LF6WMAvZW9JhIlkjRNhI1qQLu+G+ffu++uor9keyYFVVVW1trT6kiAZMZXV1tWVBXjnG4l0TGQvLk3lkqbJgWbYs3h77aZtkjRBhI1mTLn5ZQ+Zj02xubm4VUYHZZH6bmpp41cxGBqaSpcqClawRImJI1qSLX9bw/o/8t3//fozfiqjAbBreuchwmEoWKUuVBStZI0TEkKxJF3ZDJ2tsf2SHYuv0Lgsh+hgsTxZp3LKVrBEiGkjWpEuirOmZ/VEI0W16a9lK1ggRNpI16SJZI0TGIVkjRFSRrEkXyRohMg7JGiGiimRNukjWCJFxSNYIEVUka9JFskaIjEOyRoioIlmTLpI1QmQckjVCRBXJmnSRrBEi45CsESKqSNaki2SNEBmHZI0QUUWyJl0ka/oIsX8/9tD+FcRuFBHRQLJGiKgiWZMukjWpMNEA3rkP70JAkoJ6ZsyY0a9fv0cffZTB70q1+KxYsYIikKoIRi4BKScOK5K0lMgImEHJGiEiiWRNuvTW/tjHIeVXVla+/vrrpgA8awxO2cSTXuoG1EA906dPR6A8/PDDra2tB63WiixbtsxkTUtLC/HEFeF0+fLl5pCUtra2bsdPKaC4cdBKDtVfHBSGUbJGiEgiWZMuvbU/9mXIu/v373/33XfPPvtsdIZfNNilpUuXnnLKKUn1xKFCcRTGn//8Z6TG/fffT4bgtPM6rcinn35qAqWuro5I/LOGA4EtXrzYHJJCQyahvDJdhsoptWHDhsGDB1PPa6+91vkgmP+cOXMGxFi/fn36gyYYUskaISKJZE269Nb+2GcxTcA43HrrraTtjz/+2EQDdnfpkksu4VJBQUH3lIEfijc3N993331UOGXKFKaA087rtCKLFi2iCJSXlzc0NCC2CM8cOCCw2traoqKinTt3bt68+aabbsLzxhtv3LhxY3Z2dl5ens11NxQGrVP56tWrBw0aRJ0vv/xynKiKw/xnzZplsmbVqlWd+4uuwAD2yrKVrBEibCRr0qW39sc+i2mCurq6Y445hrQ9evRoJxoYGVIyyqBdTfTr9/zzzzc1NXVDGTgoSHEqueeee6jw9ttvLy0ttTo9j2QQBj4LFiywMAoLC4nW/4zHuoCsQXghYtavXz9p0iQ8J06cuGbNGlROTk5OZWVlN4K3gLlJqqqqqBx5lCiq/Byqv+givbVsmU3JGiFCRbImXXprf+yz2IB8+eWXJhogKyvLHjCQjEnJ9uQDrrjiijg9ARwDzoadetcOYEZzoDhZYerUqVR4yy23FBcX04SpDcPcwDs/oITeffddCwOtgIKJkzUWKtolPz8fZfOnP/0JzxtuuGHTpk179uxBPFGkubnZ35DhaoC4dg1qpvWKiorc3FzkUUlJSX19Pa37Pf0FLdqu+1sAhln8Vx2ex+EKAyJZI0QkkaxJl97aH/sm5Es2aATBM888Y6IBrrzySixkYsQNubl///5HHHEE9oEDB1ZVVbmPVCzdvv7666eeeqoVPOeccxYsWECFOHDJfDheuHCh+QwYMODOO+8kMUyZMoVTZE1RURFtIR1wW7FixWWXXRarqd8pp5xi32LBzmtjY+M777xjlygeJ2sAt9bWVtz27t1LnfaBGoIMYYHCQI0hNaz4smXLqPnII48cPHiw1Q/ooQkTJhA//OEPf9i9e7d9Q3ns2LE0xE1SXV1txekgWe2zzz6zq+vXr7eYqZBOUQ914u8+MqN1/B955BGOp0+fTnEbClp/9tlncfYP1HPPPWff4GGgiKe8vPzRRx/ltOs/GYsqdL9Xli0TJFkjRKhI1qRLb+2PfRMyJWkblXD++eeTPidOnMgrZGVlMTKohMcff5zTSZMm/d///R8Hixcvdh/lMG6k3ph7B6677joUhvO56667vAsHOPHEE+1DosmTJyNBSBL4IzXsqh+rigiRPp3LGmsLeWSTi3jC054G1dfXYwQr/uSTT9oBlTc3N1MP0gQZYUaD09tuu42DMWPG0F+gRbuEXqHCTz75hONjjz02ruD1119PwFT78ccfm4Vg8LevSJ988slmdLzyyism6SBxMKmcIDl46KGHTE36u3xYQd9tZiVrhIgYkjXp0lv7Y9+EvpMvGQd7HjN37tyLL76Yg2nTppGMa2pq7As3CxcuvOiiiziYPn06ezpSgG3d9Er//v2ffvrpPXv27Nq1C8XAKcYHH3yQ1E7CtqcacMUVVyxdujQnJ2f58uVIKGsOWVNYWEhD27dvN7cpU6Z8+eWXVPXGG2/8+Mc/xvLyyy8zRzTauawx6A6qgrAttltvvbWsrAxJRDB1dXVWnB7Nnz8fuVNZWUnTSBbUCXaao1E6gqSzz8hg5MiRe/fuxY1XsyxYsKC6utp90eeEE06gR/Trt7/9rVnQgtT54Ycf2mlFRQX+9957r50yDtSPkLLenXXWWfSOvrz33nvmcPnllzNQhLFixYoLL7zQjBQnhqRdPkzorWUrWSNE2EjWpEtv7Y99ExuNJUuWkDt/+MMfrlq1aubMmRyjTtAWdnzppZdi/8tf/sIxigTRgBJCLnAK77///rZt27Yc4Nlnn8VIcZQH2d1+QvWLX/zCrmZnZ+/cuRMRM3ToUOw333xzQUEBFV5zzTWcTpw4cevWrZsPYMoAFUJV0BVZgwU7V03W3HbbbSZriAQRY8Uff/zxHTt25ObmlpaW0jSyCePAgQOREZs2bSIArhKk/VZr+PDhJSUl6JLy8vJY6X5IIixvvfWWnX788cd0x8I2i8kghsVO0W34WzxHH300I2D+//znP7GMGDGCGNxATZgwwfrOkDL+u3fv/vnPf479zjvvrKqqQpwdtvdqby1byRohwkayJl16a3/sgyAC2J3J+nfffTe5E22xIYZpjilTppx55pkczJ07d/369SZ9gPxKGrZ/JGbIkCGmV5AC5GDUAAnb3HAgwZ944okck8JRDKRzxEReXh6e9pWRm266KT8/nwpHjRoVK5SctWvXMlPoCTvthqwBRIwVf+mll4gEOUW7SAp7jjJ58uSsrCzEBLERJK/2jxoPGzaMCCsqKoqLi2Ol+7355ptY5syZwzFCkCJ79uyxX5WbAwKIjjsRRm3420daV199tfM3WYNswp+AY779Zs2aRRhIH3zoZk5OziuvvILdHjsx7JI1kjVCRAzJmnSRrHE4ETBixAhy5zPPPIM6IeVbxrXPiZA4qBaM5Nof/ehHWN599926ujp7lIKFq4gAsj65H+lAJsYOCxcuLCkpsZpffvllihcWFqIkGHOc7dnPzTff3J4wysrMLRUIGiqfN2+enXZD1pCHnC5BOiCtiKS+vp6OOEmH4DAFwyUiX7NmDXa6T3MoD4KPlW4XeVhMbXAV/YGz/Xs55kBD9PFf//qXnTI4+N9yyy0cI+OcvwmjM844g+PKykr78A7JZQOFhUrwfP7557FTvCu/hI8wkjVCRBXJmnSRrHHQ8ZaWFvIuiRNIzOR1Uj4J/qijjjLjU089ZXZ2c/t50Z/+9Kfq6mpXivxNYkZJoB5QCa+++ipGJJGV+sUvfsHp2LFjkTuMNokZKG7PgSZPnky16AD7YsrMmTPXrVtnH8Fs3bo1K4al+QBlzWuvvYZMwdjc3IyyefrppzHSX5pGTGAnwr179z788MPYhw0bRnP4FxQUxEq3y5rc3FzrpokSnFFCGM0BC6d+WcMlGzr75Zf5v/nmm1iogZoJ0r6y7QbKvqCDp9kpLlkjWSNEJJGsSRfJGgdbM5nSPTYg+6IeSOFkYkvq//d//7dx40Z7hlFSUvL6669j/PGPf8wp2K+ZUDDPPvss+gCHv/3tb/bUYdq0aTt27CABIAI4BdIzGoXRxn7xxRebm5M19gnXd77znenTp69evZoAFi9ejCgZPnw4pQgJHZDOh1B+WfPGG2+gq9A0ra2thI1mOvroo7HTr0WLFhEhAuKBBx4w51Syxn63ZR8hUUlNTQ2jZA6dyJrbb7/d+ZtKc7LGVA5cfvnljDnhMVD2hRuQrJGsESKqSNaki2SNgQLYv38/G7T9y3X33XcfCZ50CxyQWdE0d9xxR3Z2NkkXoWAPJOyTKYzIGvb3cePGxdJuB8aPH2+fTFEPRewnyn5OPPFEaubAZA0Jm1f7P70Tee655/bu3UtUTijg3EVZg4xwsgbVZcURENSGpqH7XELuoDCsX44BAwY89NBDHCSVNVhMCyJr7AEPLTqHRFmDv323hl47fydr7FkUqihxoE466ST7yf0tt9xC/JI1kjVCRA/JmnSRrDFMAdQd+D8T3nvvPZI3GbexsZEsu3PnzqlTpy5btoxNHBFAQiUTk4DthznPPvss6RlBsGPHjscee8y+cwM//vGPZ86cuXnzZnQPaZ56SMb4TJ8+/fjjj8ehf//+N954Y1ZWln3X5Oabbyadu6pmzZp13nnnxWpq/2nSb3/72xUrVhAVQYL7Em7ivzLscJ2yf+7Pno6YrEE8WfG3336b4sgaMhOzb519//33kWjIlJEjR/7ud79bvny5+/YMI0Al9N2Kv/HGGwRgsubMM8/kFmLEaNE50BdkjYt2z549+BMJx3feeafzt4dPyBr8MRIeYTz11FM2mAwUYbiBkqyRrBEiqkjWpItkjYECILXbY4Zdu3aReu2jmZaWFpJuUVERRlIyGZ00jCevHOfk5NiXXu0LIogSFAw6ZsuWLVu3buXVvhnD1s/V+tg/90L9WDZu3Ghyh+SNguF4w4YNnJLUkU1MhKuKejgA3HJzc2mUekgkHOzevRsjAgJLJ7KGq1RL/BQnDNSAabW44sw7/TJFQnMW4fbt2ylIkBYhwRA/wosuUxw7A4U/44AbMdNB6qdCHGzEysrKMPLaRX/6RQzYuWrfKHJh8HrppZciayZPnixZI1kjRCSRrEkXyRrDKQDSKiKGrN8Q+w8T7B/qtcSMEQd7sIHcQQOVlpba0wh2dvwZQFNF9iVfXknkpGccuEoRqkIt4YOdq6gHnE0bkfXxpAY0h7+qmKRp/8ddcLAv2JLOLSROkQiIDEvwSWUNdq4SAM5ES8xoNUA8JRbnlUvUjJ0IXbtEyCvBkMMYBCohPDqOG8NiKofaTHLRTSrEAQs+9Bcjr130tw4yAjREuwwjsoaxQoGtXr3aPh2bP38+fcHt8LxXQbJGiKgiWZMukjWGS+okWtI2aRX5wlCAKRsTLuRgvwJwztjxx41T8rGlcPI0Wdw+tLLHIVYVPiaegPRMmkd2ABndHgXhTBEK4mZV8cqxq8ocqAeLC9XrSUewcxUfnOvq6mg9VXE65frlegEWoYE6YRyohDitOCNADdTMKZcYB/pIheaAnYao0DXXFX9O0T32jx0/8cQTCBpEVW5urv1A7Pjjj0dyER5hpOp15KHjdF+yRojoIVmTLr21P/ZBLKmTU4HEzzhYpucAu6kBMzpnLM7Z3DhlDNnoyd+8kqSdEjLMBztXgXSOP4kfLMf7qzK3uKrMwdQAFn9UiWDnqsUJBy3uIiQq9EdihPjjYMWBU3DHXLIWnQMHh+oPtLVixQr7gdiQIUPOPPNM+98VjjjiiHnz5iFxEFgEQ0EL+3CDjjMpkjVCRA/JmnTprf2xb0KK9eNZO9o9UzJnO2CLB0vPHDCedtVwPn4Hh/PkgFPnBnFVtdcS87EDMybFHBx+Y9LiZqE5a93addjVTnA1dJFEf1pB1uzduxdl8+tf/9p+cI6g4fjzzz/ftWtXSUkJqRRVhHMs5MMOhkiyRohIIlmTLr21P0YbS8/gnSfD8zhYYvaceiN/ew33eNO0iGQhWZaVleXk5Gzfvt2+h8TBnj17ioqKamL/D9fhfKNK1ggRVSRr0kWyRvQ1kDXchAiXurq6ioqKwsLCvBgclMf+x6jm5mbyaM/rrb6DZI0QUUWyJl0ka0QfxJRNa+zbRYibmhgcNMa+Un2YaxqQrBEiqkjWpItkjeibmLIhX8Z9xRjjYa5poLeWrWSNEGEjWZMuvbU/CtEVUDBxeBcObyRrhIgqkjXpIlkjRMYhWSNEVJGsSRfJGiEyDskaIaKKZE26SNYIkXFI1ggRVSRr0iVxf2SH0jcYhOizsDxZpJI1QkQSyZp08cuaqth/77w/9u/3x76dKTIYJtHwzkVUYE5ZpCxVFqxkjRARQ7ImXdgNPVlz/hC2SP1F4K909KCSUYNKRh9bctbg9r9R7ZY4H/1F5O/8IZI1QkQJyZp0cbKmuLi4pKSE93/2HynXi8yEuWMG23Xqb0dY4qnasdX+LTvPQ2Q4NsUsVRYsy1ayRogoIVmTLuyGLS0tpD22yKKiotLS0vLy8gqRsTB9pLqcnJzi8WdY4slZ8zkzW1ZW5nmIzIdZZqkyrSxbFm9zc7NkjRDRQLImXb6N/beCDQ0NvOdjrwRv4xSZCfKlsLAwOzu7aNwwSzzbli3Oy8uTYI0YtlpZtqiKHvvPzCVrhAgbyZp0sW8gtra2NjY2ukfc+sAic+G9O9lu586dTtZkL1/Ce/q9e/dqWqOBrVDgmGXb0tKCqpCsESIaSNYEgPtthfvPd0Tmsm/fPpRNTk5O4WVDLfHsWrW8srLS8p/nJCIBC9b9btFbzCEjWSNE2EjWBAY7o4gA5DnSTF5enntak7Pmc4QOWdDyn4ge3hoOH8kaIcJGskaIDpBgGhoa8vPznazJXbuqtra2x75+ISKMZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHJGtEeEjWCBE2kjVCdECyRoSHZI0QYSNZI0QHEmVNzprPJWtEIEjWCBE2kjVC/A+Ey/79+0kzeXl5Ttbs+WJlTU1Na2vrN9984/kJ0S0ka4QIG8kaITzQNGSXr+6d4FKO/6983NC2pkY9sBHpIFkjRNhI1gjRjmma5ubm6o1rXcrx/1W+9ixX8ZGyEd1GskaIsJGsEaId+/ipoaGhpKSk4NYrXNaxv+JLflr079z6+np9w0akg2SNEGEjWSNEOyZrEC4FBQWbFsxzWcf+tj/5IOlHXxwWaSJZI0TYSNYI0Q5ihdTS0NBQVFS0fv36nZP+n0s8hb86dd2qz5E7pB+kj2SN6DaSNUKEjWSNEB7ffPNNc3NzVVVVdnb2qrmzXeLJenTqli1bysvL9+3bpx9DiXSQrBEibCRrhPD49ttv29ra6uvr8/Pz16xZs2PiJWSdwl+dunr5stzcXH0CJdJHskaIsJGsCRJynshoyC779u2rqKjYtm3b6jdeKR37/U2P3bN58+aysrLGxkb7BEpED28Bh49kjRBhI1kTDOyM33zzTdV1Py8bPUh/+tNfBv2xbFm8PSNuJGuECBvJmgAwTdPa2soWyQ5VX19fF4MDkXHU1tZWVlbm5eVt3rx53bp1mzZtys3NraioqKmp8TxE5uNfoSxb+yeke0DZSNYIETaSNQHAbtjW1tbQ0MD+SP4rLy/nVWQoTF9JSQmyZseOHVu2bNm+fTuJp7i4WNMaPZhTYNmyeHvmi1OSNUKEjWRNAPA+r6WlhXfz7I9FRUWlpaVKgRlNWVkZOqagoABxk5+fzzEW75qICixSlioLlmXL4mUJs5C9JR0akjVChI1kTQCwG+7bt++rr75if+SNflVVVW1trT6EymiYQVLd3r17eeXYs4qowPJkWlmqLFiWLYu3Z369L1kjRNhI1gSAX9bwLpBNs7m5uVVkOLx9N7xzES1YpCxVFqxkjRBRQrImAPyyhvd/TU1N+/fvx/itEKJPwvJkkbJUWbCSNUJECcmaAPDLGtsf2aTYOr3LQog+BsuTRRq3bCVrhIgAkjUBkChremB/FEKkQ68sW8kaIcJGsiYAJGuEyDgka4SIJJI1ASBZI0TGIVkjRCSRrAkAyRohMg7JGiEiiWRNAEjWCJFxSNYIEUkkawJAskaIjEOyRohIIlkTAJI1QmQckjVCRBLJmgCQrBEi45CsESKSSNYEgGRNJIn9a7TxeNdYOTFWrlzpnR8GWJf9g5DRSNYIEUkkawIgkP2RbHHuuedapkzMHBi5hEOGJhXCnjFjRiwt/o+xY8fefffdmzZt8pz6BoQKK1asmDBhwuDBgy3UI4888rLLLnvuueeqqqq4yvyaHTeOsXiFe4S4kWQYZ86cyY3nXQ4Bf5dJwO0D5MNzOkS8wr13PweybA8VyRohwkayJgDS3x/Z3NnXzjnnHNLGsmXLKO62ew44Xb58OZdwsKRilzIF69306dNjaTEJ48aNCzUrdx1CraystIlICpfa2tpaW1vtdMmSJZz2QDo07GawkRwwYMDZMSySU0891SSX5xoc1qjrcnNzM11mlJBTnE6cOBGHQ2oXZ0LtdvGgoFOSNUJED8maAEhzf2RPZ1Oj1JgxY9joP/nkk5aWFlcDV8kiixcv5hIOuO3fv79X0kD3cL174IEH6MLIkSOLioqKi4u3b9++YMGCW265BSOQlbuRVOy5RVAPsQhgw4YNyAXq7N+//9SpUz/44IOcGNhnz5591VVXXXLJJU1NTQ0NDbGo++Fg/7Npz8yI3QwPPfQQTY8aNaqkpKS0tHTnzp1XX301FiRXGJFYo67LNTU1dJl2TVFdf/31XRF29iSS+aI2nMvKyg6peBjQaDrLtntI1ggRNpI1AZDm/shGz1vh2tpaUj4bPcmeFGL5CUwTLFq0iEs4kFT8oqfvY72rq6tDJdCFYcOGbdmyZdu2bciaXbt25ebmIuNMSUyfPv1Qx+3RRx+lIO/7GSVOvQvdgqbLy8tPOeUUKjzhhBPWrFmzdevWzTE2bdrEa3Z2NtHiw0xVV1fjBu+88w5do4Nptt5F7Ga49957afqMM85ww4jqsngQOoErG0aGW27v3r3WBIKGm5BBqKqqYjQYioMKOy7ZsxmmGE+Gizu868VDgn6ls2y7h2SNEGEjWRMAae6PODc3N7PLn3nmmWz98+bNI2dYpgT2O3IA6ZNLOFRUVPTM/hsUhEpSZFjuuOMOunD66aeTg1E2iAawxPzWW29xCchzXUxvuPEu/+GHH6bUmDFjGMB0lA0Fyaz2FGTgwIErV640KUOEqBmDOHNyckjqZGJmIRZvPyIn3/eM0HQ3w913303TQ4cOzcrKsjHk1eL54IMPGIoAg6FRauOWq6ystCby8/M5hoKCAnRecXFx58IOOzNlz2b+/Oc/I2KAQSssLOxK8fCwfknWCBExJGsCIM390YqT0YcPH87W/+abb7LpO1lDuq2vr58/fz6XeINOWiUr2Htfsu+MGTOOO+44jn/yk5+sWLHCigBZedy4cdi5OnPmTCxeY//9LxG6UkceeeTEiRPJLn4H6NzHfX9548aN1go+U6dOpZQ5+KF3JFqy4O23344nyXjnzp1s5WRH6uTYErNJuqeeesqpE16JgZ4CrVjv8AHqxM2OHeeccw52fMC6b2WpxLqDD68WlR/8qY0pGDRoED6PPfYYxdExiJiioiIGvKysrKSkhATMAVXV1NQ4WfPGG29gMVlDPYsWLbJGYe7cuVj8XwMHnBlMhsuNWCq7F5wP3OxmmDJlCnUykgTJGBLnqlWrYuH0YyTJkcgIO6VdwqBOptIaoh6KTJo0CSMO2G187JIDi/M59dRTFy9eTN9jVfZj7ug+jBgxglOiNRXOCFCK2rgVzRMYBybOOznAgw8+iGdicWIgWlecsoynC4wDs/MGwMaKY2aZ7pjDoUKLTDq1lY4exP3Z2NjIuHEnhAo9pb9MmWSNiBjsGCxJ7mfvvCNslVzl1TsPE8maALD9kZ06HVlD2kC12MQnypp58+ZxCQfyK+/X7Tut5Bte/ezevdt2T/cTHmPChAmWNtjEE0uRIRAoXCWYzn2oBOz7yzRhqcXhWrF+GVj8sgbpRhfoIJt7dXU1x3v27NmyZYt9yeaaa64xiZA0BvelYwaHOu3YMWbMGOz0fc6cOZ7pAIRKbBw8+uijiRFySj6rq6szZzTNjh07EDSER76xpwvkPIYd7IDumLPJGntWZE34YZpsphix2LTE+9BHeprKnhinX9YMGzaMHQQ1vGbNGhOF1113XV5enn1MGaum3zPPPGMHf/jDHyhL35nEuFkDmqNH1hyvCIVEn2effdYOaBRnem2fmd57770mpDAmThndX7p0qXdygPvvv98VnzZtmhVPHAQDBUPYQPxmiWuFyeVq3Fh1BUoxs+izkjHHOZER9l/xOd/fc9Z31555rLMwZX1c1jC23Rjevg83z4svvuidiLTpGVlD/dTDm0/vPBmSNQHA/thjssYe2tuXi+GJJ56gRTJH//79OeV9MFUtWbKE44svvphM89lnn5100klkPiqkKsscJ5988oIFC2iR/H3fffdhITdY2oNOfKgE7PvLQM0bNmwgMVx11VVm4So1+DdBTv2yhgRMwiZIPLHTtdLYl14nT57M1VGjRtmbZothwIABzz//PJmb4mxA9hUcoBSqiNjcEyD0HD4IDqI1n4suumjt2rUYs7KyGAozPvTQQxahF1wMi3DXrl3ms23btsLCQsQBRsaEfIMDr8ApsRE8XTBnJsu68+qrr5qFNE8MtLto0SLG0IyffvoptQHHgwYNoi0466yz/vnPfyJBEu2zZ8+mobg43c1gsuaII44YMWIEU9DeQEzlrFixgjXPzcM4mPHYY48lDPQZw8XA0haTiJ0BWbduHQPIEP3qV7/Ccv3117sbYGzsWSCj/frrrzP4MHPmzIEDB7bX2K8foocu08ro0aM55d6gOWpGOXFKKWQlc0op2uVeBRqyJ5E33ngjHUTLMj7MtRUnMCblrrvusuL/+Mc/8Aem3mYcOYsDbhybD53irsPTLNzkhO2/67oCE0qdhJp/1mAnMsL+Q9bkjPnul2cemzVicNYd121/5A5kDQNIMF5YfQmGlIHdt2751/Nn7d/X1I1B9sPU23zBFVdc4Vl7D8LoXNZw1aI12H69CxnCJ5984oXer9/dd9/tWTuCT1Bz0bmsCYrPP/+cViRrQqd95feUrCHj0oRllMsvv5x7iDRDUrcEz71LLrHH/uQh0tKePXusCDv49u3bsSOAli9fjpLgFCh75ZVXYieV0ij2TnxmzZrFO8uFCxdyDPhY61YKCJV87N/76B1pmzTmZA29s0cywAECIj8/32QNC4wsSIuxytq/KcJWSOX0gp5++OGHZresieXmm2/m9Gc/+9nmzZsLCgro+zXXXIPl/PPP9xek/gsuuAA7SZQ36KQQf4SW3si17VXHnniZUolza5+M2C5PdxhPc2ayTE4hIDh9+OGH/e1u3LjR1AACEWFBT019IkZtXmiIEUu005GkAfhljXHMMcdceOGFFGQETJAxvLRlV//2t78xQSROe0LG9GE88cQTic0/uVSCPTs7m7lbv359rOj/Bh8HonK6jQrpMiPgHrcwZbRrV7k3rGbKMuxME/qDAJCeXGXjY0yooaioyD3soUeI9VjpfugVf2DckxjRMfg4Kfn3v//d3XX2mOrjjz+Ou+u6AsNLtQS5Z9T/np2E/Yes+feY720aOXjpsGM+eWsuo81Q2D3phdVnsLudga1d+AaRl48bWvf2S21NjRg7GWqbI4OUyY6UmFCRC31B1nQOwR999NHeyaFA17z+++jd/iadBSPAuZCsiRSs8/RlDQnAZA33WSeyhuSNp30v4emnn966dSsJgHxmCR7pQIKB3/zmN5wC7+nvvPNOUgu5h93fjEm5+uqrSc+d+1x11VVkFwvm+OOPd62Tq8yBq2R9f/c5TpQ1rnfs5jRKVrO+P/TQQwygxYDnli1bqNlaIYeRd3/0ox9xyfJiTk7OTTfdxCmyBjdyJ9LQkiXpMK6gfRwzdepUxsGfAjlghNFqDJpVTtZEFqRKk3QHKeZkzdy5cxlbdImdJgZ83XXXYWfEmDXU2F//+lfzBFQpbigYwn7yySc9a8yOJkBpdS5rTj/99E2bNtEKMAXAgBAMwbvw0DHYUQAMF8b777/f7El54YUXmAv7FpcNvn1peseOHcRJW0cddRSXrBV3ExIMk25Kd/jw4ZQCGwGmCTlF79jpTNZMnDgxKysLkcRkmSJhRhgBE6xDhgyhII0a1MMAYofPPvuMO9+OV65cSeX0i6EeNmwYFlqPu+u6AoPJzUAwX5x+1OLFi0ljn8bgIFS4vZGMH330ERs0HWQwkTXcb0x3X4N1yi1RMX+2k2UmblobGxjtuAVC15gLbl3v/L//RRZAhsqaNINkKLyjGAxCL3Y5pmqCkTWs5fZFeADuYe+CT9bYFwqBA+9asg+hzGIcd9xxnvUA/qtOxHDgmWKkklCSNQHACg9E1thjfG4ONvo4WYOC4dJ5553Hm0uyo6UE8hBpgDQD9t2UyZMns01ziv2ll1667LLLkDXY77vvPrLd+++/z3EqEATkpwULFnjnySCTkSDJ5RyTVl3rHJgDaYx9kA3RbXn0rnNZQ/6233kRKm9e2eUtTkQGKdCyNSmNO5hkhpbiElsnSgij9ZpIuERgtG4j89RTT8UVRKxgR+EhQax1C48DG2E8p02bhs8xxxzDIHdd1jAdxGynZN+4du3pEW4WMGmMEb722mvtKc7o0aOpikt4xtm5JfzDCC5U+7zmtNNOW7duHemfFlEeaAhuIfI04+8ebLBn0SLtMv4Mu/0yPBWmMEygIBcQDURFtdYXWnGyxiSafa7EkBK/iSGmDDfuQAaQ6UDQ0DvqdLL1j3/8I/FwFVxxanvvvfesOFIGlUYTQKc4xQ6IACbdjv13nakl7p+4u64r4G+yZsfInntaE42/pE9ukj7bYN4TE2onqdTuE4dn7Yjfh6po16+lgMq9y7EH2Pgjubxrsda9ayk+hPIXd1BJ3FV/F4jBjK5Cju3AERenqUDHQSOJ64gZXSmumiWpfMGYaPePg5+kkRh+qeFwmsNkjdM0htMrcbLGnOOwSxAnX8BakazpOUyXpClrSI3PP/88U9W/f3+2WvuYhi2D/Mrme8IJJ3AJdUKOcckb4cIbcZIHkB6w3HzzzawcdnySB2mJnLd27Vry9IABA8gu9nsZ0uHq1asRELz/xofU+MUXX2zYsIFGST/2AVZSH05JOdxJ9p1c+0aLtU6LWKCwsPDrr78m+7rNjl4klTWudzRkH8EQvOVm2opV1u/tt9/mbT1JGi1CDYti/3gPuHbtR+PkYCvIyNhjKpaWvyAx22JjlJyosvA4IL3Z0xqSqMmmk08+mcqdjx/C9sua119/nUEDkyPoBn+7yDLb78yNTM8A2rwwTRdeeCGXGHAkQqKdMU8la+xpDXPErJH76R2V0yi9YKi5l5ysmTVrFleJlkvcRfa13xtuuCHVDUAkbrdFqXCzURZBTF/efPNNszPXNtSmS5hWNAp6zq6iiriTKUKcNNoU+6cLqcTuWDfFBGzFmUGGhTBipfuhb6gZf7qA3b49g94lNjSW+fjvOntaQ6hxd11XsMEknp2SNd36Q9w0bV3PimAwyYVJE2pScPZrAj9+/cFaYHL9FiC1+/OuSRy/XKBmfySmDOIqMbjUSQrvJMi4Joy4wGjUOzqAX/bZKvOHTfG45uJa4TSuI1ji4sc/MTBIZYdOupkIAYB7QmOfB4HJC6dU7CrYrmuKxC9rXMGYVzt2lRrs1K5atXbq5JGVdVoqKZI1AcDCTlPWkI3Yx9mv7XOQk0466d1338UOpB/7gjCbO7qETOOe1syePZtTMijwVhuLPa3hrS0O48ePJ0+z4yMaUDbkEu6SSy+9FDcqnDt3LkmUxPb3v//99NNPf/TRRylIaidVdOLDOqQSkzVkFNc6BbEAFlJF57IGgYUywPL+++9ff/31VvCyyy4jWhIkdnIewWOkyzNnziQvUgMZ2tQPECq5kxGz5xZEQgCckhHdh2i//OUvt23bRkGq5diMibIGUA9kX0YVLbhs2bIhQ4bgiRBEPfh/mM0xW8O4ceNssqxC9ArZl14//vjjZpk2bRrB4EMkJkaBRUsaRruwgzDFSBkW549//GMuIX2Y90Q7wcflaY79sgZZSYWMFeOJkbvOPsjwh/fqq6/SLxtAfAjMnriwfSAgmNzly5dPnz79hz/8IaqFqac2psC0AoOPqmhsbKQsg2/fv4E4XcK0tiuDnTvtp/7MER1nfhlk4gGOUTn2idUtt9xiM0VUrjijRw32aR3FEetMB6P6l7/8xWYcsUj9zA7H4L/rLNR58+bF3XVdgbEiMO4lPa3pxl/R7b8rX/c5t4cNO0ujE4kQR9dTaSwdd8jH/icWSUlM9qno3LOTIE1veScxCMmvWiDOgar8HYl7cmPg07lqiSPRIXG4jFR26KSbcZjyiNMTfrFisoYdzC4ZWOyjKL+nPXRxqsWw4hx0Llwka3oIMnc6soZNga2fdMvm/vbbb9v7+zjY37nEW3O2exKkyRqSFomcDR24a7Ega6hkzZo1TgEYvCcmGbCDL1269Ac/+IFn9UEuJ8mRbCjOO+9UPryrJpfYh1DsL651kpz5HFTWJAVxQ82kLrrGOFDt6tWr7cGJH/cbYxIwFTLUluCJhGHhlIK8p3e/A3cgL+wDvqSyhgjtAQzjg4ZDW5x//vlWMJFzzjmHpJsoa1AhJgf9/O53vyM2DljMBEwmPvHEE+2SQbLHTkiJdoxE5b+RiNkva8joSBDqZHhRD3ji4Ppi9RAe9XND0mV7IoV8+c53vmNX/fzmN7/hKnqFvnz44YdoGu/CAV555RU74A7xy5rbbrsNC3PHuJko9zN27FjiqaurM1lz66232kwx0XGyZuvWrSaM4sCIMPXLGv9dZ8PbPVmDP4GhKVefdhTphF7zfgBNxmsPQEP2VZ7FfRiG5YMPPlg5/W6/oNkx8ZLVb7zCgmXi0IXcWtx1B83BfrqeSpPmY/8OyQ3gWX3YXWHEqQ0/ncfceZBc8gcWdwpe8wfwX0XQJA2b0Y5rsfOOJMbfPljJ5EsqO3R9LkyLxKkWpAlGExlOl/hB09iDlkQBlBQq9HsmIlnTQ7Cq05Q1pCV2WPIK2XHlypV33XWX++Huscce+6c//WnVqlVs7uRd8kHFgX8Jbc6cOZySroC7FguyhtsCB6SJfXmWxXDPPfeQErCTPKiE3eqmm26yD00AhfTkk0+yQ1GK4Mk6JJikPiRRmgO77UhLrnUyjXnShbgEw1CkkjWjRo264YYbWMyICTpODORyihMJK3/ZsmW8uaeno0ePvuSSSxYtWpSXl2cFGYc4WUOGoyzploJsuOTgCy64gIJjxoy57777srKy7JdWSWWNjb+lSfvwjmDeeuut3//+9+4X2kBVNlD0l9bNaF+aAfIurTz++OMWMM4vvPACAdvjBEaMIuQAkqj9pgzdcO211yJAGbrq6upEO4MQdyMRp8kaezJnvW448P9smAP+fllDuxyb7uGNNbKVrr377rsoMBMuyF80HG70iwgZHHxQz++///748eNNHDMICxcutP0LTNYQttMldJMZ4bYBRtj+VUPj7LPPphfuaQ2yhpjpL3eOFbcPobi10KPcnH/961+dwkOM/uMf/0Btc4n6GWGz++862/fnz5/fDVnzn9gvoejXuqFHcbOxZJb3LAjBPg7DwvJcNWOaCZqt1/3yo+efRv+RWphrppIBNEnN/tOJRIijk1Rq+5ifVPnYoKqkEsFB/KmUTaIs8NN5vvc/sPEfO/wWIvQ3REjtHUtGJ31J7IhkTSokawKAVZ2mrLHPQcgWpDc2d5IryYPtHsgZpBk2d4yIBlICTZAGOMWZ5EdiA/Z63Eha3BZkJnZ8CpIJKEieJjGQt6iNIliQEZYqAAuvXKJmpBW5LScnJ6kPrXMVqJnWWcz+1mkLf+oh3ySVNThsiEFZqxYLm6N1jTrpF4OAc03sJ9+MA0KBS/SIprHQQSx0hwirqqoIGDsO1EOXCZ6sTD2dFGRUqTxO1oAFSXGcGUM8qYRq8WfcqIRXLtE7OoIbHScGmuCVvnNKW520S2fxIWCmGDs1u3mxOqnEb+cA/6SyhuGliPWaUowYN4/nEesIsoaGiBwfXjnGYh9OMcKpJpc66ReV40P8LjzrC6PKMX2hIHUSGwNOQRsB0hs+FjwTip1SjJgpNupE1uCAMwOCkYYYBxq1COkFUE+7LNq6lfsKI6c4M6RMB6cUx8JxF++6rsCYUEn7YA4/mn7RNFVRoTAYfwZ8/fr1WX9/ZMfESz596TnU7ZIlS9DcNub2pJBhZNi7nh0hlTPGuMzdST52JGb3OFJV0nnBg/aIq1Ytr4mepF7vKAZ6hVvXjjnoXIqlItaP/3UkMf44B0cqOxy0mw5TG3F6IlGssPbtkoGlix9COToXLpI1PQS5JB1ZA/iTa0nMbBZsKOzmbLLsKez7HJAtOOYmIJdbkiA3sMs7KQCkRnZ/MoqlE15ZPJS1/dpSEc5cwgcLUKc1gQU7rVMPb7/IFkl97H02OYkDclJi64RE2caOv0x2iZarZMr2XTIrix7RR+sm/SVaq4p3fiQnDoiWJnCw+PGhO2ymWAgGf8JgHEiuuNE0AViq67wg2ZFu0kpc/uOUmGmXMJAXeFLcFIk/VBsommYiiIGGLHIisTyNW9J2qZMIKcX82tjixiUbMWImMP98MdcmR/w3kgXJ8JoIoNdUSF6J8+FGMhmBD68c28cE9JrxSTW5dgNw63KDmbym4xYM6Y3u4EbA9Ig66TLdoVN0mVPCAIYCTyvFK/5213FHUbObKSyc2jhjYUDoKQmSwDilOco6rBIu0RwN4dDFu64rMCY2mHkjj6FaDqiZySUeYTBZTBPz/sUXX5BO1q1bxw1jNzP3icllN+YoEu5hO3aQNRNTeKpUSrryjg4Ql48/SfZvx/mzOwEkNhdXiSNRFvg5aL6nLQuY18SOx/UFB79i86ucpHSlI4nxxzk4UtnhoN30Q6fAPbAxhQEmUNwzGLsKx8X++x2TIH5ZYwXdt4CN9pIHytqx0z321WM75ZVjyZrQYX9MU9ZYxrIHFSYayB8u65BU2ErIHKQlthI2dHYc8oTlDCxAqmBfJjlhxJMDdnzWBmW5D0hUeFLQ3LDYJaAtS1RcJf+5qpL6sJcBB4mt0wRGewMXl2hJqHhaYqNfQJ1UTkIiF9IWqZdBQ9BQEPCnFSokBhcAxwwC6YdIbFdlNEhCVIsnAVgknRdkZOhm0vyHhQAIw+k2S+QkaZenqYqmLU9zQNNUSIuUwthJu4wVfbTkjd3NC6cYaTHOjj+9S3z8wODYTeJ6bZLFu3ygF5QlMAvP1YMbzsSZanIZGUbe+XD/mAMSh2OKgI0hDnSHIN0I2Fy4W9duWtN8SAewmaJaCnJKDVYcB8rGDSDFgQipwQYcDumu6wr40y71F48aRD1USyV0Xzi4JRhbm1Zw08FA2WqNuz/JN8yadxLLu1i8Ex+pUimJ35+nyesU9+djrmLxl437aMY+3/ELAuJJGgMkygI/Xcn31sGkbomNxmkLHIjWO4nBVRd5VzoSF6EF42/CEWs5uayxat2sWbuphsWkSRxOYZisifuAyWkXv6yBpJ9DuavU6ZkOgL9dYovwTKmf90jWBIDtj2y73ZY1wAZhyoZdg1SBLiGFAG9n2XPZXCzr4MMrx7iRD9jc2V+AgmQXMwI7PpVQkDRARsHCJoUb/hxjwU6OAfYpMo1VTtjUj2cqn9he177ZpWqdvnPq3+ysX3hylcEhJIM6EWfESZKjTic1eCUMgrFcSAw480pZBgGsCBW6SGiaAKgBMHZeEIdUs+NCpcL22SwrY/xNmvDK5m4pnLaA7tO0RUKXO2mXocOZIgyOf17ovtUWZ6cS/JPGSYS0hb+/1zZuho2eBWPhWT3Y3aVUk2s3QJyP6wunbgzpsn8E8KcsFk7pBXUiNShIEbsKbqYIntO44jaArlGKQzp3XVegpxSka6WjBxE29dtgCoPxYUBsWm327Zaz+wQHbxw74iWcGHH5Hv3hXeiIP7t7phgkV5IxB0644EmdZjT8mgZIz0gBCnqXY3jXYlgWT4rn0fGLuo6k2sVqi1MnJi8cnjUGp/6A4wbE38RBO2L424pJlw7DZfZEnIgxTMoYceOZiHtCY7gnN2BKhQN7uAJOi0CcrAGzOOI0iv+qvx5wkshfm58kIyUOFbc/piNrwLYSyxC26QNbie3sbs+17QY3cEZnAbZ4/KmESMDSgO1EvHKMBTvVAm7+yqETHy7ZVWsosXWzeP05gHNwIQHHNGFFqDOulLVCo553rBecGtYdiGsXulIwri0/VgMVUoqOM/gkcoMZIWZrC2wQXIUHbddKcewGAYdO7KnixIh/e59Tj7YF4w8v7hJN0FDc5HLViPPh1SarvSe+vlgM1oTBKZ5Wrb8j4Pw58J+ag2uU+hMDay9/oEeAxeL018mp9bHrUCdtpb9sI4wb5NjMH3z5HG4gO/wPVEQnJMqa8JCsCYAA98f23Tq2xbObsIkYbh/3nA64GYkWg0ocnJobxF2CmHuHrapzHzs2UlnisEteXT7M7jl1xC55fjHMkgqv2MEKek6dghulGHawxAkcx1XlcKUg1qCHWeLwrsXwTDE8UwxOrc6kmL/hmTriXTuAZz0AFq+ZAyS6pfJJilem05rtwEg8NezUKxnDLP6rRirLIUH9kjUHxYY3bi6EcfTRR8c9qhGpsM+V/E93wkOyJgDC2B9tEzE8k+hxvAk4gGcVkUCyRqQDguagH9kI8H9ulerbMMEiWRMA2h+FyDi0bEU38H+zx0j1BVthuO//dv7zpQCRrAkA7Y9CZBxatkJEEsmaAND+KETGoWUrRCSRrAkA7Y9CZBxatkJEEsmaAND+KETGoWUrRCSRrAkA7Y9CZBxatkJEEsmaAND+KETGoWUrRCSRrAmAxP3xP936Z0+FED0Dy5NFKlkjRPSQrAkAv6yx/1xm/4F/ZVwI0QdhebJIWart/4mVZI0QEUKyJgD+J2vOH8IWqT/96S+T/s4fIlkjRGSQrAkAJ2uKi4tLSkp4/1dbW1tXV2f/V6UQoq/B8mSRslRZsCxbyRohIoNkTQCwG7a0tNTU1LBFFhUVlZaWlpeXVwgh+jAsUpYqC5Zly+Jtbm6WrBEiAkjWBMC3337b1tbW0NDAez72SmkaITICW60s26+//polzEL2lrQQImORrAkA+wZia2trY2Oje8StD6GE6LPYCgWOWbYtLS369aIQ0UCyJhjcbyt4z4e+EUJkBCxY97tFbzELITIZyZogYWcUQmQi3hoWQmQ4kjVCCCGEiAiSNUIIIYSICJI1QgghhIgIkjVCCCGEiAiSNUIIIYSICJI1QgghhIgIkjVCCCGEiAiSNUIIIYSICJI1QgghhIgIkjVCCCGEiAiSNUIIIYSIBP/97/8HMEHnJlJrnjsAAAAASUVORK5CYII=" style="margin-left: auto;margin-right: auto"><p>Importantly, ClassifyR implements a number of methods for
110
+classification using different kinds of changes in measurements between
111
+classes. Most classifiers work with features where the means are
112
+different. In addition to changes in means (DM),
113
+<strong>ClassifyR</strong> also allows for classification using
114
+differential variability (DV; changes in scale) and differential
115
+distribution (DD; changes in location and/or scale).</p>
116
+<div class="section level3">
117
+<h3 id="case-study-diagnosing-asthma">Case Study: Diagnosing Asthma<a class="anchor" aria-label="anchor" href="#case-study-diagnosing-asthma"></a>
118
+</h3>
119
+<p>To demonstrate some key features of ClassifyR, a data set consisting
120
+of the 2000 most variably expressed genes and 190 people will be used to
121
+quickly obtain results. The journal article corresponding to the data
122
+set was published in <em>Scientific Reports</em> in 2018 and is titled
123
+<a href="http://www.nature.com/articles/s41598-018-27189-4" class="external-link">A Nasal
124
+Brush-based Classifier of Asthma Identified by Machine Learning Analysis
125
+of Nasal RNA Sequence Data</a>.</p>
126
+<p>Load the package.</p>
127
+<div class="sourceCode" id="cb1"><pre class="downlit sourceCode r">
128
+<code class="sourceCode R"><span><span class="kw"><a href="https://rdrr.io/r/base/library.html" class="external-link">library</a></span><span class="op">(</span><span class="va"><a href="https://sydneybiox.github.io/ClassifyR/">ClassifyR</a></span><span class="op">)</span></span></code></pre></div>
129
+<p>A glimpse at the RNA measurements and sample classes.</p>
130
+<div class="sourceCode" id="cb2"><pre class="downlit sourceCode r">
131
+<code class="sourceCode R"><span><span class="fu"><a href="https://rdrr.io/r/utils/data.html" class="external-link">data</a></span><span class="op">(</span><span class="va">asthma</span><span class="op">)</span> <span class="co"># Contains measurements and classes variables.</span></span>
132
+<span><span class="va">measurements</span><span class="op">[</span><span class="fl">1</span><span class="op">:</span><span class="fl">5</span>, <span class="fl">1</span><span class="op">:</span><span class="fl">5</span><span class="op">]</span></span></code></pre></div>
133
+<pre><code><span><span class="co">##            HBB BPIFA1  XIST FCGR3B HBA2</span></span>
134
+<span><span class="co">## Sample 1  9.72  14.06 12.28  11.42 7.83</span></span>
135
+<span><span class="co">## Sample 2 11.98  13.89  6.35  13.25 9.42</span></span>
136
+<span><span class="co">## Sample 3 12.15  17.44 10.21   7.87 9.68</span></span>
137
+<span><span class="co">## Sample 4 10.60  11.87  6.27  14.75 8.96</span></span>
138
+<span><span class="co">## Sample 5  8.18  15.01 11.21   6.77 6.43</span></span></code></pre>
139
+<div class="sourceCode" id="cb4"><pre class="downlit sourceCode r">
140
+<code class="sourceCode R"><span><span class="fu"><a href="https://rdrr.io/r/utils/head.html" class="external-link">head</a></span><span class="op">(</span><span class="va">classes</span><span class="op">)</span></span></code></pre></div>
141
+<pre><code><span><span class="co">## [1] No  No  No  No  Yes No </span></span>
142
+<span><span class="co">## Levels: No Yes</span></span></code></pre>
143
+<p>The numeric matrix variable <em>measurements</em> stores the
144
+normalised values of the RNA gene abundances for each sample and the
145
+factor vector <em>classes</em> identifies which class the samples belong
146
+to. The measurements were normalised using <strong>DESeq2</strong>’s
147
+<em>varianceStabilizingTransformation</em> function, which produces
148
+<span class="math inline">\(log_2\)</span>-like data.</p>
149
+<p>For more complex data sets with multiple kinds of experiments
150
+(e.g. DNA methylation, copy number, gene expression on the same set of
151
+samples) a <a href="https://bioconductor.org/packages/release/bioc/html/MultiAssayExperiment.html" class="external-link"><em>MultiAssayExperiment</em></a>
152
+is recommended for data storage and supported by
153
+<strong>ClassifyR</strong>’s methods.</p>
154
+</div>
155
+</div>
156
+<div class="section level2">
157
+<h2 id="quick-start-crossvalidate-function">Quick Start: <em>crossValidate</em> Function<a class="anchor" aria-label="anchor" href="#quick-start-crossvalidate-function"></a>
158
+</h2>
159
+<p>The <em>crossValidate</em> function offers a quick and simple way to
160
+start analysing a dataset in ClassifyR. It is a wrapper for
161
+<em>runTests</em>, the core model building and testing function of
162
+ClassifyR. <em>crossValidate</em> must be supplied with
163
+<em>measurements</em>, a simple tabular data container or a list-like
164
+structure of such related tabular data on common samples. The classes of
165
+it may be <em>matrix</em>, <em>data.frame</em>, <em>DataFrame</em>,
166
+<em>MultiAssayExperiment</em> or <em>list</em> of <em>data.frames</em>.
167
+For a dataset with <span class="math inline">\(n\)</span> observations
168
+and <span class="math inline">\(p\)</span> variables, the
169
+<em>crossValidate</em> function will accept inputs of the following
170
+shapes:</p>
171
+<table class="table">
172
+<colgroup>
173
+<col width="25%">
174
+<col width="37%">
175
+<col width="37%">
176
+</colgroup>
177
+<thead><tr class="header">
178
+<th>Data Type</th>
179
+<th align="center"><span class="math inline">\(n \times p\)</span></th>
180
+<th align="center"><span class="math inline">\(p \times n\)</span></th>
181
+</tr></thead>
182
+<tbody>
183
+<tr class="odd">
184
+<td><span style="font-family: 'Courier New', monospace;">matrix</span></td>
185
+<td align="center">✔</td>
186
+<td align="center"></td>
187
+</tr>
188
+<tr class="even">
189
+<td><span style="font-family: 'Courier New', monospace;">data.frame</span></td>
190
+<td align="center">✔</td>
191
+<td align="center"></td>
192
+</tr>
193
+<tr class="odd">
194
+<td><span style="font-family: 'Courier New', monospace;">DataFrame</span></td>
195
+<td align="center">✔</td>
196
+<td align="center"></td>
197
+</tr>
198
+<tr class="even">
199
+<td><span style="font-family: 'Courier New', monospace;">MultiAssayExperiment</span></td>
200
+<td align="center"></td>
201
+<td align="center">✔</td>
202
+</tr>
203
+<tr class="odd">
204
+<td>
205
+<span style="font-family: 'Courier New', monospace;">list</span> of
206
+<span style="font-family: 'Courier New', monospace;">data.frame</span>s</td>
207
+<td align="center">✔</td>
208
+<td align="center"></td>
209
+</tr>
210
+</tbody>
211
+</table>
212
+<p><em>crossValidate</em> must also be supplied with <em>outcome</em>,
213
+which represents the prediction to be made in a variety of possible
214
+ways.</p>
215
+<ul>
216
+<li>A <em>factor</em> that contains the class label for each
217
+observation. <em>classes</em> must be of length <span class="math inline">\(n\)</span>.</li>
218
+<li>A <em>character</em> of length 1 that matches a column name in a
219
+data frame which holds the classes. The classes will automatically be
220
+removed before training is done.</li>
221
+<li>A <em>Surv</em> object of the same length as the number of samples
222
+in the data which contains information about the time and censoring of
223
+the samples.</li>
224
+<li>A <em>character</em> vector of length 2 or 3 that each match a
225
+column name in a data frame which holds information about the time and
226
+censoring of the samples. The time-to-event columns will automatically
227
+be removed before training is done.</li>
228
+</ul>
229
+<p>The type of classifier used can be changed with the
230
+<em>classifier</em> argument. The default is a random forest, which
231
+seamlessly handles categorical and numerical data. A full list of
232
+classifiers can be seen by running <em>?crossValidate</em>. A feature
233
+selection step can be performed before classification using
234
+<em>nFeatures</em> and <em>selectionMethod</em>, which is a t-test by
235
+default. Similarly, the number of folds and number of repeats for cross
236
+validation can be changed with the <em>nFolds</em> and <em>nRepeats</em>
237
+arguments. If wanted, <em>nCores</em> can be specified to run the cross
238
+validation in parallel. To perform 5-fold cross-validation of a Support
239
+Vector Machine with 2 repeats:</p>
240
+<div class="sourceCode" id="cb6"><pre class="downlit sourceCode r">
241
+<code class="sourceCode R"><span><span class="va">result</span> <span class="op">&lt;-</span> <span class="fu"><a href="../reference/crossValidate.html">crossValidate</a></span><span class="op">(</span><span class="va">measurements</span>, <span class="va">classes</span>, classifier <span class="op">=</span> <span class="st">"SVM"</span>,</span>
242
+<span>                        nFeatures <span class="op">=</span> <span class="fl">20</span>, nFolds <span class="op">=</span> <span class="fl">5</span>, nRepeats <span class="op">=</span> <span class="fl">2</span>, nCores <span class="op">=</span> <span class="fl">1</span><span class="op">)</span></span></code></pre></div>
243
+<pre><code><span><span class="co">## Processing sample set 10.</span></span></code></pre>
244
+<div class="sourceCode" id="cb8"><pre class="downlit sourceCode r">
245
+<code class="sourceCode R"><span><span class="fu"><a href="../reference/performancePlot.html">performancePlot</a></span><span class="op">(</span><span class="va">result</span><span class="op">)</span></span></code></pre></div>
246
+<pre><code><span><span class="co">## Warning in .local(results, ...): Balanced Accuracy not found in all elements of results. Calculating it now.</span></span></code></pre>
247
+<p><img src="ClassifyR_files/figure-html/unnamed-chunk-5-1.png" width="700"></p>
248
+<div class="section level3">
249
+<h3 id="data-integration-with-crossvalidate">Data Integration with crossValidate<a class="anchor" aria-label="anchor" href="#data-integration-with-crossvalidate"></a>
250
+</h3>
251
+<p><em>crossValidate</em> also allows data from multiple sources to be
252
+integrated into a single model. The integration method can be specified
253
+with <em>multiViewMethod</em> argument. In this example, suppose the
254
+first 10 variables in the asthma data set are from a certain source and
255
+the remaining 1990 variables are from a second source. To integrate
256
+multiple data sets, each variable must be labeled with the data set it
257
+came from. This is done in a different manner depending on the data type
258
+of <em>measurements</em>.</p>
259
+<p>If using Bioconductor’s <em>DataFrame</em>, this can be specified
260
+using <em>mcols</em>. In the column metadata, each feature must have an
261
+<em>assay</em> and a <em>feature</em> name.</p>
262
+<div class="sourceCode" id="cb10"><pre class="downlit sourceCode r">
263
+<code class="sourceCode R"><span><span class="va">measurementsDF</span> <span class="op">&lt;-</span> <span class="fu"><a href="https://rdrr.io/pkg/S4Vectors/man/DataFrame-class.html" class="external-link">DataFrame</a></span><span class="op">(</span><span class="va">measurements</span><span class="op">)</span></span>
264
+<span><span class="fu"><a href="https://rdrr.io/pkg/S4Vectors/man/Vector-class.html" class="external-link">mcols</a></span><span class="op">(</span><span class="va">measurementsDF</span><span class="op">)</span> <span class="op">&lt;-</span> <span class="fu"><a href="https://rdrr.io/r/base/data.frame.html" class="external-link">data.frame</a></span><span class="op">(</span></span>
265
+<span>  assay <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/rep.html" class="external-link">rep</a></span><span class="op">(</span><span class="fu"><a href="https://rdrr.io/r/base/c.html" class="external-link">c</a></span><span class="op">(</span><span class="st">"assay_1"</span>, <span class="st">"assay_2"</span><span class="op">)</span>, times <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/c.html" class="external-link">c</a></span><span class="op">(</span><span class="fl">10</span>, <span class="fl">1990</span><span class="op">)</span><span class="op">)</span>,</span>
266
+<span>  feature <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/colnames.html" class="external-link">colnames</a></span><span class="op">(</span><span class="va">measurementsDF</span><span class="op">)</span></span>
267
+<span><span class="op">)</span></span>
268
+<span></span>
269
+<span><span class="va">result</span> <span class="op">&lt;-</span> <span class="fu"><a href="../reference/crossValidate.html">crossValidate</a></span><span class="op">(</span><span class="va">measurementsDF</span>, <span class="va">classes</span>, classifier <span class="op">=</span> <span class="st">"SVM"</span>, nFolds <span class="op">=</span> <span class="fl">5</span>,</span>
270
+<span>                        nRepeats <span class="op">=</span> <span class="fl">3</span>, multiViewMethod <span class="op">=</span> <span class="st">"merge"</span><span class="op">)</span></span></code></pre></div>
271
+<pre><code><span><span class="co">## Processing sample set 10.</span></span>
272
+<span><span class="co">## Processing sample set 10.</span></span>
273
+<span><span class="co">## Processing sample set 10.</span></span></code></pre>
274
+<div class="sourceCode" id="cb12"><pre class="downlit sourceCode r">
275
+<code class="sourceCode R"><span><span class="fu"><a href="../reference/performancePlot.html">performancePlot</a></span><span class="op">(</span><span class="va">result</span>, characteristicsList <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html" class="external-link">list</a></span><span class="op">(</span>x <span class="op">=</span> <span class="st">"Assay Name"</span><span class="op">)</span><span class="op">)</span></span></code></pre></div>
276
+<pre><code><span><span class="co">## Warning in .local(results, ...): Balanced Accuracy not found in all elements of results. Calculating it now.</span></span></code></pre>
277
+<p><img src="ClassifyR_files/figure-html/unnamed-chunk-6-1.png" width="700"></p>
278
+<p>If using a list of <em>data.frame</em>s, the name of each element in
279
+the list will be used as the assay name.</p>
280
+<div class="sourceCode" id="cb14"><pre class="downlit sourceCode r">
281
+<code class="sourceCode R"><span><span class="co"># Assigns first 10 variables to dataset_1, and the rest to dataset_2</span></span>
282
+<span><span class="va">measurementsList</span> <span class="op">&lt;-</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html" class="external-link">list</a></span><span class="op">(</span></span>
283
+<span>  <span class="op">(</span><span class="va">measurements</span> <span class="op">|&gt;</span> <span class="fu"><a href="https://rdrr.io/r/base/as.data.frame.html" class="external-link">as.data.frame</a></span><span class="op">(</span><span class="op">)</span><span class="op">)</span><span class="op">[</span><span class="fl">1</span><span class="op">:</span><span class="fl">10</span><span class="op">]</span>,</span>
284
+<span>  <span class="op">(</span><span class="va">measurements</span> <span class="op">|&gt;</span> <span class="fu"><a href="https://rdrr.io/r/base/as.data.frame.html" class="external-link">as.data.frame</a></span><span class="op">(</span><span class="op">)</span><span class="op">)</span><span class="op">[</span><span class="fl">11</span><span class="op">:</span><span class="fl">2000</span><span class="op">]</span></span>
285
+<span><span class="op">)</span></span>
286
+<span><span class="fu"><a href="https://rdrr.io/r/base/names.html" class="external-link">names</a></span><span class="op">(</span><span class="va">measurementsList</span><span class="op">)</span> <span class="op">&lt;-</span> <span class="fu"><a href="https://rdrr.io/r/base/c.html" class="external-link">c</a></span><span class="op">(</span><span class="st">"assay_1"</span>, <span class="st">"assay_2"</span><span class="op">)</span></span>
287
+<span></span>
288
+<span><span class="va">result</span> <span class="op">&lt;-</span> <span class="fu"><a href="../reference/crossValidate.html">crossValidate</a></span><span class="op">(</span><span class="va">measurementsList</span>, <span class="va">classes</span>, classifier <span class="op">=</span> <span class="st">"SVM"</span>, nFolds <span class="op">=</span> <span class="fl">5</span>,</span>
289
+<span>                        nRepeats <span class="op">=</span> <span class="fl">3</span>, multiViewMethod <span class="op">=</span> <span class="st">"merge"</span><span class="op">)</span></span></code></pre></div>
290
+<pre><code><span><span class="co">## Processing sample set 10.</span></span>
291
+<span><span class="co">## Processing sample set 10.</span></span>
292
+<span><span class="co">## Processing sample set 10.</span></span></code></pre>
293
+<div class="sourceCode" id="cb16"><pre class="downlit sourceCode r">
294
+<code class="sourceCode R"><span><span class="fu"><a href="../reference/performancePlot.html">performancePlot</a></span><span class="op">(</span><span class="va">result</span>, characteristicsList <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html" class="external-link">list</a></span><span class="op">(</span>x <span class="op">=</span> <span class="st">"Assay Name"</span><span class="op">)</span><span class="op">)</span></span></code></pre></div>
295
+<pre><code><span><span class="co">## Warning in .local(results, ...): Balanced Accuracy not found in all elements of results. Calculating it now.</span></span></code></pre>
296
+<p><img src="ClassifyR_files/figure-html/unnamed-chunk-7-1.png" width="700"></p>
297
+</div>
298
+</div>
299
+<div class="section level2">
300
+<h2 id="a-more-detailed-look-at-classifyr">A More Detailed Look at ClassifyR<a class="anchor" aria-label="anchor" href="#a-more-detailed-look-at-classifyr"></a>
301
+</h2>
302
+<p>In the following sections, some of the most useful functions provided
303
+in <strong>ClassifyR</strong> will be demonstrated. However, a user
304
+could wrap any feature selection, training, or prediction function to
305
+the classification framework, as long as it meets some simple rules
306
+about the input and return parameters. See the appendix section of this
307
+guide titled “Rules for New Functions” for a description of these.</p>
308
+<div class="section level3">
309
+<h3 id="comparison-to-existing-classification-frameworks">Comparison to Existing Classification Frameworks<a class="anchor" aria-label="anchor" href="#comparison-to-existing-classification-frameworks"></a>
310
+</h3>
311
+<p>There are a few other frameworks for classification in R. The table
312
+below provides a comparison of which features they offer.</p>
313
+<table class="table">
314
+<colgroup>
315
+<col width="8%">
316
+<col width="10%">
317
+<col width="8%">
318
+<col width="10%">
319
+<col width="10%">
320
+<col width="11%">
321
+<col width="14%">
322
+<col width="12%">
323
+<col width="12%">
324
+</colgroup>
325
+<thead><tr class="header">
326
+<th>Package</th>
327
+<th>Run User-defined Classifiers</th>
328
+<th>Parallel Execution on any OS</th>
329
+<th>Parameter Tuning</th>
330
+<th>Intel DAAL Performance Metrics</th>
331
+<th>Ranking and Selection Plots</th>
332
+<th>Class Distribution Plot</th>
333
+<th>Sample-wise Error Heatmap</th>
334
+<th>Direct Support for MultiAssayExperiment Input</th>
335
+</tr></thead>
336
+<tbody>
337
+<tr class="odd">
338
+<td><strong>ClassifyR</strong></td>
339
+<td>Yes</td>
340
+<td>Yes</td>
341
+<td>Yes</td>
342
+<td>Yes</td>
343
+<td>Yes</td>
344
+<td>Yes</td>
345
+<td>Yes</td>
346
+<td>Yes</td>
347
+</tr>
348
+<tr class="even">
349
+<td>caret</td>
350
+<td>Yes</td>
351
+<td>Yes</td>
352
+<td>Yes</td>
353
+<td>No</td>
354
+<td>No</td>
355
+<td>No</td>
356
+<td>No</td>
357
+<td>No</td>
358
+</tr>
359
+<tr class="odd">
360
+<td>MLInterfaces</td>
361
+<td>Yes</td>
362
+<td>No</td>
363
+<td>No</td>
364
+<td>No</td>
365
+<td>No</td>
366
+<td>No</td>
367
+<td>No</td>
368
+<td>No</td>
369
+</tr>
370
+<tr class="even">
371
+<td>MCRestimate</td>
372
+<td>Yes</td>
373
+<td>No</td>
374
+<td>Yes</td>
375
+<td>No</td>
376
+<td>No</td>
377
+<td>No</td>
378
+<td>No</td>
379
+<td>No</td>
380
+</tr>
381
+<tr class="odd">
382
+<td>CMA</td>
383
+<td>No</td>
384
+<td>No</td>
385
+<td>Yes</td>
386
+<td>No</td>
387
+<td>No</td>
388
+<td>No</td>
389
+<td>No</td>
390
+<td>No</td>
391
+</tr>
392
+</tbody>
393
+</table>
394
+</div>
395
+<div class="section level3">
396
+<h3 id="provided-functionality">Provided Functionality<a class="anchor" aria-label="anchor" href="#provided-functionality"></a>
397
+</h3>
398
+<p>Although being a cross-validation framework, a number of popular
399
+feature selection and classification functions are provided by the
400
+package which meet the requirements of functions to be used by it (see
401
+the last section).</p>
402
+<div class="section level4">
403
+<h4 id="provided-methods-for-feature-selection-and-classification">Provided Methods for Feature Selection and Classification<a class="anchor" aria-label="anchor" href="#provided-methods-for-feature-selection-and-classification"></a>
404
+</h4>
405
+<p>In the following tables, a function that is used when no function is
406
+explicitly specified by the user is shown as <span style="padding:4px; border:2px dashed #e64626;">functionName</span>.</p>
407
+<p>The functions below produce a ranking, of which different size
408
+subsets are tried and the classifier performance evaluated, to select a
409
+best subset of features, based on a criterion such as balanced accuracy
410
+rate, for example.</p>
411
+<table style="width:100%;" class="table">
412
+<colgroup>
413
+<col width="9%">
414
+<col width="62%">
415
+<col width="9%">
416
+<col width="9%">
417
+<col width="9%">
418
+</colgroup>
419
+<thead><tr class="header">
420
+<th>Function</th>
421
+<th>Description</th>
422
+<th>DM</th>
423
+<th>DV</th>
424
+<th>DD</th>
425
+</tr></thead>
426
+<tbody>
427
+<tr class="odd">
428
+<td><span style="padding:4px; border:2px dashed #e64626; font-family: 'Courier New', monospace;">differentMeansRanking</span></td>
429
+<td>t-test ranking if two classes, F-test ranking if three or more</td>
430
+<td>✔</td>
431
+<td></td>
432
+<td></td>
433
+</tr>
434
+<tr class="even">
435
+<td><span style="font-family: 'Courier New', monospace;">limmaRanking</span></td>
436
+<td>Moderated t-test ranking using variance shrinkage</td>
437
+<td>✔</td>
438
+<td></td>
439
+<td></td>
440
+</tr>
441
+<tr class="odd">
442
+<td><span style="font-family: 'Courier New', monospace;">edgeRranking</span></td>
443
+<td>Likelihood ratio test for count data ranking</td>
444
+<td>✔</td>
445
+<td></td>
446
+<td></td>
447
+</tr>
448
+<tr class="even">
449
+<td><span style="font-family: 'Courier New', monospace;">bartlettRanking</span></td>
450
+<td>Bartlett’s test non-robust ranking</td>
451
+<td></td>
452
+<td>✔</td>
453
+<td></td>
454
+</tr>
455
+<tr class="odd">
456
+<td><span style="font-family: 'Courier New', monospace;">leveneRanking</span></td>
457
+<td>Levene’s test robust ranking</td>
458
+<td></td>
459
+<td>✔</td>
460
+<td></td>
461
+</tr>
462
+<tr class="even">
463
+<td><span style="font-family: 'Courier New', monospace;">DMDranking</span></td>
464
+<td><span style="white-space: nowrap">Difference in location
465
+(mean/median) and/or scale (SD, MAD, <span class="math inline">\(Q_n\)</span>)</span></td>
466
+<td>✔</td>
467
+<td>✔</td>
468
+<td>✔</td>
469
+</tr>
470
+<tr class="odd">
471
+<td><span style="font-family: 'Courier New', monospace;">likelihoodRatioRanking</span></td>
472
+<td>Likelihood ratio (normal distribution) ranking</td>
473
+<td>✔</td>
474
+<td>✔</td>
475
+<td>✔</td>
476
+</tr>
477
+<tr class="even">
478
+<td><span style="font-family: 'Courier New', monospace;">KolmogorovSmirnovRanking</span></td>
479
+<td>Kolmogorov-Smirnov distance between distributions ranking</td>
480
+<td>✔</td>
481
+<td>✔</td>
482
+<td>✔</td>
483
+</tr>
484
+<tr class="odd">
485
+<td><span style="font-family: 'Courier New', monospace;">KullbackLeiblerRanking</span></td>
486
+<td>Kullback-Leibler distance between distributions ranking</td>
487
+<td>✔</td>
488
+<td>✔</td>
489
+<td>✔</td>
490
+</tr>
491
+</tbody>
492
+</table>
493
+<p>Likewise, a variety of classifiers is also provided.</p>
494
+<table class="table">
495
+<colgroup>
496
+<col width="9%">
497
+<col width="61%">
498
+<col width="9%">
499
+<col width="9%">
500
+<col width="9%">
501
+</colgroup>
502
+<thead><tr class="header">
503
+<th>Function(s)</th>
504
+<th>Description</th>
505
+<th>DM</th>
506
+<th>DV</th>
507
+<th>DD</th>
508
+</tr></thead>
509
+<tbody>
510
+<tr class="odd">
511
+<td>
512
+<span style="padding:1px; border:2px dashed #e64626; display:inline-block; margin-bottom: 3px; font-family: 'Courier New', monospace;">DLDAtrainInterface</span>,<br><span style="padding:1px; border:2px dashed #e64626; display:inline-block; font-family: 'Courier New', monospace;">DLDApredictInterface</span>
513
+</td>
514
+<td>Wrappers for sparsediscrim’s functions <span style="font-family: 'Courier New', monospace;">dlda</span> and
515
+<span style="font-family: 'Courier New', monospace;">predict.dlda</span>
516
+functions</td>
517
+<td>✔</td>
518
+<td></td>
519
+<td></td>
520
+</tr>
521
+<tr class="even">
522
+<td><span style="font-family: 'Courier New', monospace;">classifyInterface</span></td>
523
+<td>Wrapper for PoiClaClu’s Poisson LDA function <span style="font-family: 'Courier New', monospace;">classify</span>
524
+</td>
525
+<td>✔</td>
526
+<td></td>
527
+<td></td>
528
+</tr>
529
+<tr class="odd">
530
+<td>
531
+<span style="font-family: 'Courier New', monospace;">elasticNetGLMtrainInterface</span>,
532
+<span style="font-family: 'Courier New', monospace;">elasticNetGLMpredictInterface</span>
533
+</td>
534
+<td>Wrappers for glmnet’s elastic net GLM functions <span style="font-family: 'Courier New', monospace;">glmnet</span> and
535
+<span style="font-family: 'Courier New', monospace;">predict.glmnet</span>
536
+</td>
537
+<td>✔</td>
538
+<td></td>
539
+<td></td>
540
+</tr>
541
+<tr class="even">
542
+<td>
543
+<span style="font-family: 'Courier New', monospace;">NSCtrainInterface</span>,
544
+<span style="font-family: 'Courier New', monospace;">NSCpredictInterface</span>
545
+</td>
546
+<td>Wrappers for pamr’s Nearest Shrunken Centroid functions <span style="font-family: 'Courier New', monospace;">pamr.train</span>
547
+and <span style="font-family: 'Courier New', monospace;">pamr.predict</span>
548
+</td>
549
+<td>✔</td>
550
+<td></td>
551
+<td></td>
552
+</tr>
553
+<tr class="odd">
554
+<td><span style="font-family: 'Courier New', monospace;">fisherDiscriminant</span></td>
555
+<td>Implementation of Fisher’s LDA for departures from normality</td>
556
+<td>✔</td>
557
+<td>✔*</td>
558
+<td></td>
559
+</tr>
560
+<tr class="even">
561
+<td>
562
+<span style="font-family: 'Courier New', monospace;">mixModelsTrain</span>,
563
+<span style="font-family: 'Courier New', monospace;">mixModelsPredict</span>
564
+</td>
565
+<td>Feature-wise mixtures of normals and voting</td>
566
+<td>✔</td>
567
+<td>✔</td>
568
+<td>✔</td>
569
+</tr>
570
+<tr class="odd">
571
+<td><span style="font-family: 'Courier New', monospace;">naiveBayesKernel</span></td>
572
+<td>Feature-wise kernel density estimation and voting</td>
573
+<td>✔</td>
574
+<td>✔</td>
575
+<td>✔</td>
576
+</tr>
577
+<tr class="even">
578
+<td>
579
+<span style="font-family: 'Courier New', monospace;">randomForestTrainInterface</span>,
580
+<span style="font-family: 'Courier New', monospace;">randomForestPredictInterface</span>
581
+</td>
582
+<td>Wrapper for ranger’s functions <span style="font-family: 'Courier New', monospace;">ranger</span> and
583
+<span style="font-family: 'Courier New', monospace;">predict</span>
584
+</td>
585
+<td>✔</td>
586
+<td>✔</td>
587
+<td>✔</td>
588
+</tr>
589
+<tr class="odd">
590
+<td>
591
+<span style="font-family: 'Courier New', monospace;">extremeGradientBoostingTrainInterface</span>,
592
+<span style="font-family: 'Courier New', monospace;">extremeGradientBoostingPredictInterface</span>
593
+</td>
594
+<td>Wrapper for xgboost’s functions <span style="font-family: 'Courier New', monospace;">xgboost</span>
595
+and <span style="font-family: 'Courier New', monospace;">predict</span>
596
+</td>
597
+<td>✔</td>
598
+<td>✔</td>
599
+<td>✔</td>
600
+</tr>
601
+<tr class="even">
602
+<td><span style="font-family: 'Courier New', monospace;">kNNinterface</span></td>
603
+<td>Wrapper for class’s function <span style="font-family: 'Courier New', monospace;">knn</span>
604
+</td>
605
+<td>✔</td>
606
+<td>✔</td>
607
+<td>✔</td>
608
+</tr>
609
+<tr class="odd">
610
+<td>
611
+<span style="font-family: 'Courier New', monospace;">SVMtrainInterface</span>,
612
+<span style="font-family: 'Courier New', monospace;">SVMpredictInterface</span>
613
+</td>
614
+<td>Wrapper for e1071’s functions <span style="font-family: 'Courier New', monospace;">svm</span> and
615
+<span style="font-family: 'Courier New', monospace;">predict.svm</span>
616
+</td>
617
+<td>✔</td>
618
+<td>✔ †</td>
619
+<td>✔ †</td>
620
+</tr>
621
+</tbody>
622
+</table>
623
+<p>* If ordinary numeric measurements have been transformed to absolute
624
+deviations using <span style="font-family: 'Courier New', monospace;">subtractFromLocation</span>.<br>
625
+† If the value of <span style="font-family: 'Courier New', monospace;">kernel</span> is
626
+not <span style="font-family: 'Courier New', monospace;">“linear”</span>.</p>
627
+<p>If a desired selection or classification method is not already
628
+implemented, rules for writing functions to work with
629
+<strong>ClassifyR</strong> are outlined in the wrapper vignette. Please
630
+visit it for more information.</p>
631
+</div>
632
+<div class="section level4">
633
+<h4 id="provided-meta-feature-methods">Provided Meta-feature Methods<a class="anchor" aria-label="anchor" href="#provided-meta-feature-methods"></a>
634
+</h4>
635
+<p>A number of methods are provided for users to enable classification
636
+in a feature-set-centric or interactor-centric way. The meta-feature
637
+creation functions should be used before cross-validation is done.</p>
638
+<table class="table">
639
+<colgroup>
640
+<col width="9%">
641
+<col width="61%">
642
+<col width="14%">
643
+<col width="14%">
644
+</colgroup>
645
+<thead><tr class="header">
646
+<th>Function</th>
647
+<th>Description</th>
648
+<th align="center">Before CV</th>
649
+<th align="center">During CV</th>
650
+</tr></thead>
651
+<tbody>
652
+<tr class="odd">
653
+<td><span style="font-family: 'Courier New', monospace;">edgesToHubNetworks</span></td>
654
+<td>Takes a two-column <span style="font-family: 'Courier New', monospace;">matrix</span> or
655
+<span style="font-family: 'Courier New', monospace;">DataFrame</span>
656
+and finds all nodes with at least a minimum number of interactions</td>
657
+<td align="center">✔</td>
658
+<td align="center"></td>
659
+</tr>
660
+<tr class="even">
661
+<td><span style="font-family: 'Courier New', monospace;">featureSetSummary</span></td>
662
+<td><span style="white-space: nowrap">Considers sets of features and
663
+calculates their mean or median</span></td>
664
+<td align="center">✔</td>
665
+<td align="center"></td>
666
+</tr>
667
+<tr class="odd">
668
+<td><span style="font-family: 'Courier New', monospace;">pairsDifferencesSelection</span></td>
669
+<td>Finds a set of pairs of features whose measurement inequalities can
670
+be used for predicting with</td>
671
+<td align="center"></td>
672
+<td align="center">✔</td>
673
+</tr>
674
+<tr class="even">
675
+<td><span style="font-family: 'Courier New', monospace;">kTSPclassifier</span></td>
676
+<td>Voting classifier that uses inequalities between pairs of features
677
+to vote for one of two classes</td>
678
+<td align="center"></td>
679
+<td align="center">✔</td>
680
+</tr>
681
+</tbody>
682
+</table>
683
+</div>
684
+</div>
685
+<div class="section level3">
686
+<h3 id="fine-grained-cross-validation-and-modelling-using-runtests">Fine-grained Cross-validation and Modelling Using
687
+<em>runTests</em><a class="anchor" aria-label="anchor" href="#fine-grained-cross-validation-and-modelling-using-runtests"></a>
688
+</h3>