Browse code

Update utilities.R

Ellis Patrick authored on 05/09/2022 06:03:37 • GitHub committed on 05/09/2022 06:03:37
Showing 1 changed files

... ...
@@ -300,7 +300,7 @@
300 300
     modellingParams@trainParams@otherParams <- tuneChosen
301 301
   }
302 302
 
303
-  if(attr(modellingParams@trainParams@classifier, "name") != "previousTrained")
303
+    if (!"previousTrained" %in% attr(modellingParams@trainParams@classifier, "name")) 
304 304
     # Don't name these first two variables. Some classifier functions might use classesTrain and others use outcomeTrain.
305 305
     paramList <- list(measurementsTrain, outcomeTrain)
306 306
   else # Don't pass the measurements and classes, because a pre-existing classifier is used.
... ...
@@ -641,4 +641,4 @@
641 641
 
642 642
 .dmvnorm_diag <- function(x, mean, sigma) { # Remove once sparsediscrim is reinstated to CRAN.
643 643
   exp(sum(dnorm(x, mean=mean, sd=sqrt(sigma), log=TRUE)))
644
-}
645 644
\ No newline at end of file
645
+}