Skip to content
Snippets Groups Projects
Commit a937fcda authored by Vincent  LAVILLE's avatar Vincent LAVILLE
Browse files

Initial commit

parent 302e8c1b
No related branches found
No related tags found
No related merge requests found
#'
#' @examples
#'
#' C <- matrix(rnorm(25), 5, 5)
#' diag(C) <- rep(1, 5)
#' C[lower.tri(C)] <- t(C)[lower.tri(C)]
#' C2 <- pruneCorMatrix(C, 0.7)
#'
################################################################################
#' Calculate the mean and the variance of the exposure
#'
#' @param df is the dataframe with the cohort information
#' @param pheno is the studied outcome
#' @param expo is the studied exposure
#'
#' @return A vector of length 2 which first element is the mean and
#' second element is the variance
#'
#' @examples
#' # Case where E is quantitative
#' datafr <- data.frame(floor(rnorm(5, 5000, 2000)), runif(5, 2.5, 3), runif(5, 1.2, 1.4))
#' colnames(datafr) <- c("pheno_N", "pheno_expo_Mean", "pheno_expo_SD")
#' params <- calculateExpoParams(df = datafr, pheno = "pheno", expo = "expo")
#' # Case where E is binary
#' datafr <- data.frame(floor(rnorm(5, 5000, 2000)), floor(runif(5, 1000, 3000)))
#' colnames(datafr) <- c("pheno_N", "pheno_expo_P")
#' params <- calculateExpoParams(df = datafr, pheno = "pheno", expo = "expo")
#'
#' @export
#'
calculateExpoParams <- function(df, pheno, expo) {
if (any(grepl(paste0(pheno, "_", expo, "_P"), colnames(df)))) {
n <- df[, grepl("_N", colnames(df))]
nexp <- df[, grepl(paste0(expo, "_P"), colnames(df))]
meanval <- sum(nexp) / sum(n)
return(c(meanval, meanval * (1 - meanval)))
}
else if (any(grepl(paste0(pheno, "_", expo, "_Mean"), colnames(df))) &
any(grepl(paste0(pheno, "_", expo, "_SD"), colnames(df)))) {
n <- df[, grepl("_N", colnames(df))]
m <- df[, grepl(paste0(expo, "_Mean"), colnames(df))]
v <- df[, grepl(paste0(expo, "_SD"), colnames(df))]
return(calculateContParams(n, m, v))
}
else {
stop("Cannot calcuate exposure parameters.\nCheck columns names.")
}
}
################################################################################
#' Perform singular Value Decomposition on the correlation matrix
#'
#' @param cormat is the correlation matrix
#' @param k is the number of eigenvectors to keep.
#' Default is the correlation matrix rank.
#'
#' @return A list with
#' \describe{
#' \item{eigval}{A vector of the top \code{k} eigenvalues}
#' \item{eigvev}{A matrix of the top \code{k} eigenvectors}
#' }
#'
getMatCorSVD <- function(cormat, k = qr(cormat)$rank) {
cormat.svd <- svd(cormat, nu = 0, nv = k)
list(eigval = cormat.svd$d[1:k], eigvec = cormat.svd$v)
}
################################################################################
\ No newline at end of file
0% or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment