R/elbow.R
ca5fb59d
 # https://stackoverflow.com/questions/35194048/using-r-how-to-calculate
 #-the-distance-from-one-point-to-a-line
b881a0f0
 # http://mathworld.wolfram.com/Point-LineDistance2-Dimensional.html
16dba6f7
 # Kimberling, C. "Triangle Centers and Central Triangles." Congr.
 # Numer. 129, 1-295, 1998.
88531e8d
 .dist2d <- function(a, b, c) {
     v1 <- b - c
     v2 <- a - b
     m <- cbind(v1, v2)
     d <- abs(det(m)) / sqrt(sum(v1 * v1))
501d7a5b
     return(d)
88531e8d
 }
 
ca5fb59d
 
88531e8d
 .secondDerivativeEstimate <- function(v) {
     nv <- length(v)
     res <- rep(NA, nv)
ca5fb59d
     for (i in seq(2, nv - 1)) {
88531e8d
         res[i] <- v[i + 1] + v[i - 1] - (2 * v[i])
     }
     return(res)
 }
 
ca5fb59d
 
0b3c7f9a
 .curveElbow <- function(var, perplexity, pvalCutoff = 0.05) {
88531e8d
     len <- length(perplexity)
     a <- c(var[1], perplexity[1])
     b <- c(var[len], perplexity[len])
     res <- rep(NA, len)
     for (i in seq_along(var)) {
0b3c7f9a
         res[i] <- .dist2d(c(var[i], perplexity[i]), a, b)
88531e8d
     }
     elbow <- which.max(res)
     ix <- var > var[elbow]
0b3c7f9a
     perplexitySde <- .secondDerivativeEstimate(perplexity)
     perplexitySdeSd <- stats::sd(perplexitySde[ix], na.rm = TRUE)
41ce752b
     perplexitySdeMean <- mean(perplexitySde[ix], na.rm = TRUE)
0b3c7f9a
     perplexitySdePval <-
         stats::pnorm(perplexitySde,
             mean = perplexitySdeMean,
             sd = perplexitySdeSd,
             lower.tail = FALSE)
501d7a5b
     # other <- which(ix & perplexitySdePval < pvalCutoff)
0b3c7f9a
     return(list(elbow = var[elbow]))
ad207a44
 }