412d446b |
################################################################################# Package Dependencies
################################################################################ %!in% operation
'%!in%' <- function(x,y)!('%in%'(x,y))
################################################################################# df2mat
|
90fec3eb |
df2mat <- function(df){
# convert df into matrix
|
412d446b |
|
90fec3eb |
if(is.data.frame(df)){
|
412d446b |
|
90fec3eb |
colnames(df) <- NULL
rownames(df) <- NULL
df <- as.matrix(df)}
return(df)
|
412d446b |
}
################################################################################# checkSym
|
90fec3eb |
checkSym <- function(mat, stp){
# checks if mat is symmetric
# checks if values in mat are between (0, 1)
|
412d446b |
|
4f49cf88 |
sym_sym <- paste0(" output of ", stp)
caption_sym <- paste0(sym_sym, " is not symmetric")
|
c0c9a95f |
|
90fec3eb |
if(!isSymmetric(mat))
stop(caption)
|
c0c9a95f |
|
4f49cf88 |
c01 <- paste0(" output of ", stp)
caption_01 <- paste0(c01, " are not in (0,1)")
|
c0c9a95f |
|
90fec3eb |
if(length(table(between(mat, 0, 1)["FALSE"])) != 0)
stop(caption_01)
|
412d446b |
|
90fec3eb |
rm(caption_sym, caption_01)
|
412d446b |
}
################################################################################# checkNumeric
|
90fec3eb |
checkNumeric <- function(x, stp){
# checks if all the values in x are numeric
|
412d446b |
|
90fec3eb |
caption <- paste0(" at least one non-numeric value at ", stp)
if(!is.numeric(x))
stop(caption)
|
412d446b |
}
################################################################################# sigmoid
|
90fec3eb |
sigmoid <- function(x, p=1, q=0){
# sigmoid function
|
412d446b |
|
90fec3eb |
res <- 1/(1 + exp(-p *(x - q) ))
return(res)
|
412d446b |
}
################################################################################# calibration
|
90fec3eb |
calibration <- function(v){
|
c0c9a95f |
# perform calibration on vector v
|
412d446b |
|
90fec3eb |
average <- mean(v)
variance <- var(v)
res <- sigmoid(v, p = (1/variance), q = average)
return(res)
|
412d446b |
}
################################################################################# norm_vec
|
90fec3eb |
normalization <- function(x){
# divide the vector x by its norm2
|
412d446b |
|
90fec3eb |
res <- x/sqrt(sum(x^2))
return(res)
|
412d446b |
}
################################################################################# GaussianKernel
|
90fec3eb |
GaussianKernel <- function(x, sigma){
# calculates Gaussian kernel for matrix x
|
412d446b |
|
90fec3eb |
res <- exp(-1 * as.matrix(dist(x)^2)/sigma)
return(res)
|
412d446b |
}
################################################################################# DOM: deepOverlapMeasure
|
90fec3eb |
DOM <- function(mat){
|
412d446b |
|
90fec3eb |
# mat: matrix, squared, symmetric, values are in (0,1)
#
# value: Deep Overlap Measure (DOM) on mat
|
412d446b |
|
90fec3eb |
diag(mat) <- 0
|
412d446b |
|
90fec3eb |
degreeRow <- replicate(dim(mat)[1], rowSums(mat))
degreeCol <- t(replicate(dim(mat)[1], colSums(mat)))
degreeMin <- pmin(degreeRow, degreeCol)
rm(degreeRow, degreeCol)
|
412d446b |
|
90fec3eb |
degreeRow <- replicate(dim(mat)[1], rowSums(mat)^2)
degreeCol <- t(replicate(dim(mat)[1], colSums(mat)^2))
degreeMin2 <- pmin(degreeRow, degreeCol)
|
412d446b |
|
90fec3eb |
numerator <- mat + (mat %^% 2) + (mat %^% 3)
denominator <- degreeMin2 + degreeMin + (1 - mat)
|
412d446b |
|
90fec3eb |
res <- numerator/denominator
diag(res) <- 1
|
412d446b |
|
90fec3eb |
rm(degreeCol, degreeRow, degreeMin, degreeMin2)
return(as.matrix(res))
|
412d446b |
}
################################################################################# TOM: Topological Overlap Measure
|
90fec3eb |
TOM <- function(mat){
# mat: matrix, squared, symmetric, values are in (0,1)
# Niloofar Aghaieabiane
# October 2021
# value: Topology Overlap Matrix (TOM) on mat
|
412d446b |
|
90fec3eb |
diag(mat) <- 0
|
412d446b |
|
90fec3eb |
degreeRow <- replicate(dim(mat)[1], rowSums(mat))
degreeCol <- t(replicate(dim(mat)[1], colSums(mat)))
degreeMin <- pmin(degreeRow, degreeCol)
|
412d446b |
|
90fec3eb |
numerator <- (mat %^% 2) + mat
denominator <- degreeMin + (1 - mat)
|
412d446b |
|
90fec3eb |
res <- numerator/denominator
diag(res) <- 1
|
412d446b |
|
90fec3eb |
rm(degreeCol, degreeRow, degreeMin)
return(as.matrix(res))
|
412d446b |
}
################################################################################# adjacencyMatrix
|
90fec3eb |
adjacencyMatrix <- function(expData, calibration = FALSE, norm = TRUE,
tom = TRUE, saveAdja = FALSE,
adjaNameFile = "adjacency.RData",
hm = "adjaHeatMap.png"){
if(!is.data.frame(expData) && !is.matrix(expData)){
stop(" the expressoion input must be eighter a data frame or a matrix")}
if(ncol(expData) >= nrow(expData)){
warning("number of genes is smaller than the samples,
|
412d446b |
are you sure that rows denote genes??", call. = FALSE)}
|
90fec3eb |
checkNumeric(expData, "expression input")
|
412d446b |
|
90fec3eb |
if(is.data.frame(expData)){
expData <- df2mat(expData)
colnames(expData) <- NULL
rownames(expData) <- NULL }
|
412d446b |
|
90fec3eb |
expData <- t(expData)
|
412d446b |
|
90fec3eb |
if(calibration == TRUE){
message("calibration...")
expData <- as.data.frame(lapply(as.data.frame(expData), calibration))
expData <- df2mat(expData)}
|
412d446b |
|
90fec3eb |
if(norm == TRUE){
message("normalization...")
expData <- as.data.frame(lapply(as.data.frame(expData), normalization))
expData <- df2mat(expData)}
|
412d446b |
|
90fec3eb |
message("Gaussian kernel...")
message("it may take time...")
totalDis <- dist(t(as.matrix(expData)), method = "euclidean")
adja <- GaussianKernel( x = t(as.matrix(expData)), sigma = var(totalDis))
rm(totalDis, expData)
checkSym(adja, "Gussian kernel")
|
412d446b |
|
90fec3eb |
adja <- df2mat(adja)
|
412d446b |
|
90fec3eb |
if(tom == TRUE){
message("TOM...\n it may take time...")
adja <- TOM(adja)
checkSym(adja, "TOM")
|
412d446b |
|
90fec3eb |
}
|
412d446b |
|
90fec3eb |
diag(adja) <- 0
|
412d446b |
|
90fec3eb |
if(saveAdja){
if(!is.character(adjaNameFile)){
warning("adjaNamFile is not string", call. = FALSE)
temp <- paste0("using following name \n ", " adjacency.RData")
message(temp)
adjaNameFile <- "adjacency.RData"}
|
412d446b |
|
90fec3eb |
save(adja, file = adjaNameFile)
message("adjancency matrix is stored") }
|
412d446b |
|
90fec3eb |
if(!is.null(hm)){
hm_plt <- SGCP_plot_heatMap(adja, tit = "Adjacency Heatmap",
xname = "genes", yname = "genes")
jpeg(hm)
show(hm_plt)
dev.off()
|
c0c9a95f |
rm(hm_plt)
}
|
412d446b |
|
90fec3eb |
message("network is created, done!...\n")
return(adja)
|
412d446b |
}
|