Skip to content

Commit

Permalink
Moved MCA_Checks to HelperChecks.R
Browse files Browse the repository at this point in the history
  • Loading branch information
ChristinaSchmidt1 committed Nov 6, 2024
1 parent 3cdd7de commit 11aa752
Show file tree
Hide file tree
Showing 2 changed files with 213 additions and 212 deletions.
213 changes: 213 additions & 0 deletions R/HelperChecks.R
Original file line number Diff line number Diff line change
Expand Up @@ -634,3 +634,216 @@ CheckInput_ORA <- function(InputData,
return(invisible(PathwayFile))
}


################################################################################################
### ### ### MCA Helper function: Internal Function to check function input ### ### ###
################################################################################################

#' Check input parameters
#'
#' @param InputData_C1 Passed to main function MCA. If not avaliable can be set to NULL.
#' @param InputData_C2 Passed to main function MCA. If not avaliable can be set to NULL.
#' @param InputData_Intra Passed to main function MCA. If not avaliable can be set to NULL.
#' @param InputData_CoRe Passed to main function MCA. If not avaliable can be set to NULL.
#' @param SettingsInfo_C1 Passed to main function MCA. If not avaliable can be set to NULL.
#' @param SettingsInfo_C2 Passed to main function MCA. If not avaliable can be set to NULL.
#' @param SettingsInfo_Intra Passed to main function MCA. If not avaliable can be set to NULL.
#' @param SettingsInfo_CoRe Passed to main function MCA. If not avaliable can be set to NULL.
#' @param BackgroundMethod Passed to main function MCA.
#' @param FeatureID Passed to main function MCA.
#' @param SaveAs_Table Passed to main function PreProcessing(). If not avaliable can be set to NULL.
#'
#' @param Function Name of the MetaProViz Function that is checked.
#' @param InputList
#'
#'
#' @keywords Input check
#' @noRd
#'
#'

CheckInput_MCA <- function(InputData_C1,
InputData_C2,
InputData_CoRe,
InputData_Intra,
SettingsInfo_C1,
SettingsInfo_C2,
SettingsInfo_CoRe,
SettingsInfo_Intra,
BackgroundMethod,
FeatureID,
SaveAs_Table
){
## ------------ Create log file ----------- ##
MetaProViz_Init()

#------------- InputData
if(is.null(InputData_C1)==FALSE){
if(class(InputData_C1) != "data.frame"| class(InputData_C2) != "data.frame"){
stop("InputData_C1 and InputData_C2 should be a data.frame. It's currently a ", paste(class(InputData_C1)), paste(class(InputData_C2)), ".",sep = "")
}
if(length(InputData_C1[duplicated(InputData_C1[[FeatureID]]), FeatureID]) > 0){
stop("Duplicated FeatureIDs of InputData_C1, whilst features must be unique")
}
if(length(InputData_C2[duplicated(InputData_C2[[FeatureID]]), FeatureID]) > 0){
stop("Duplicated FeatureIDs of InputData_C2, whilst features must be unique")
}

}else{
if(class(InputData_Intra) != "data.frame"| class(InputData_CoRe) != "data.frame"){
stop("InputData_Intra and InputData_CoRe should be a data.frame. It's currently a ", paste(class(InputData_Intra)), paste(class(InputData_CoRe)), ".",sep = "")
}
if(length(InputData_Intra[duplicated(InputData_Intra[[FeatureID]]), FeatureID]) > 0){
stop("Duplicated FeatureIDs of InputData_Intra, whilst features must be unique")
}
if(length(InputData_CoRe[duplicated(InputData_CoRe[[FeatureID]]), FeatureID]) > 0){
stop("Duplicated FeatureIDs of InputData_CoRe, whilst features must be unique")
}
}


#------------- SettingsInfo
if(is.null(SettingsInfo_C1)==FALSE){
## C1
#ValueCol
if("ValueCol" %in% names(SettingsInfo_C1)){
if(SettingsInfo_C1[["ValueCol"]] %in% colnames(InputData_C1)== FALSE){
stop("The ", SettingsInfo_C1[["ValueCol"]], " column selected as ValueCol in SettingsInfo_C1 was not found in InputData_C1. Please check your input.")
}
}
#StatCol
if("StatCol" %in% names(SettingsInfo_C1)){
if(SettingsInfo_C1[["StatCol"]] %in% colnames(InputData_C1)== FALSE){
stop("The ", SettingsInfo_C1[["StatCol"]], " column selected as StatCol in SettingsInfo_C1 was not found in InputData_C1. Please check your input.")
}
}

## C2
#ValueCol
if("ValueCol" %in% names(SettingsInfo_C2)){
if(SettingsInfo_C2[["ValueCol"]] %in% colnames(InputData_C2)== FALSE){
stop("The ", SettingsInfo_C2[["ValueCol"]], " column selected as ValueCol in SettingsInfo_C2 was not found in InputData_C2. Please check your input.")
}
}
#StatCol
if("StatCol" %in% names(SettingsInfo_C2)){
if(SettingsInfo_C2[["StatCol"]] %in% colnames(InputData_C2)== FALSE){
stop("The ", SettingsInfo_C2[["StatCol"]], " column selected as StatCol in SettingsInfo_C2 was not found in InputData_C2. Please check your input.")
}
}
}else{
## Intra
#ValueCol
if("ValueCol" %in% names(SettingsInfo_Intra)){
if(SettingsInfo_Intra[["ValueCol"]] %in% colnames(InputData_Intra)== FALSE){
stop("The ", SettingsInfo_Intra[["ValueCol"]], " column selected as ValueCol in SettingsInfo_Intra was not found in InputData_Intra. Please check your input.")
}
}
#StatCol
if("StatCol" %in% names(SettingsInfo_Intra)){
if(SettingsInfo_Intra[["StatCol"]] %in% colnames(InputData_Intra)== FALSE){
stop("The ", SettingsInfo_Intra[["StatCol"]], " column selected as StatCol in SettingsInfo_Intra was not found in InputData_Intra. Please check your input.")
}
}

## CoRe
#ValueCol
if("ValueCol" %in% names(SettingsInfo_CoRe)){
if(SettingsInfo_CoRe[["ValueCol"]] %in% colnames(InputData_CoRe)== FALSE){
stop("The ", SettingsInfo_CoRe[["ValueCol"]], " column selected as ValueCol in SettingsInfo_CoRe was not found in InputData_CoRe. Please check your input.")
}
}
#StatCol
if("StatCol" %in% names(SettingsInfo_CoRe)){
if(SettingsInfo_CoRe[["StatCol"]] %in% colnames(InputData_CoRe)== FALSE){
stop("The ", SettingsInfo_CoRe[["StatCol"]], " column selected as StatCol in SettingsInfo_CoRe was not found in InputData_CoRe. Please check your input.")
}
}

#StatCol
if("DirectionCol" %in% names(SettingsInfo_CoRe)){
if(SettingsInfo_CoRe[["DirectionCol"]] %in% colnames(InputData_CoRe)== FALSE){
stop("The ", SettingsInfo_CoRe[["DirectionCol"]], " column selected as DirectionCol in SettingsInfo_CoRe was not found in InputData_CoRe. Please check your input.")
}
}

}

#------------- SettingsInfo Cutoffs:
if(is.null(SettingsInfo_C1)==FALSE){
if(is.na(as.numeric(SettingsInfo_C1[["StatCutoff"]])) == TRUE |as.numeric(SettingsInfo_C1[["StatCutoff"]]) > 1 | as.numeric(SettingsInfo_C1[["StatCutoff"]]) < 0){
stop("Check input. The selected StatCutoff in SettingsInfo_C1 should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_C2[["StatCutoff"]])) == TRUE |as.numeric(SettingsInfo_C2[["StatCutoff"]]) > 1 | as.numeric(SettingsInfo_C2[["StatCutoff"]]) < 0){
stop("Check input. The selected StatCutoff in SettingsInfo_C2 should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_C1[["ValueCutoff"]])) == TRUE){
stop("Check input. The selected ValueCutoff in SettingsInfo_C1 should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_C2[["ValueCutoff"]])) == TRUE){
stop("Check input. The selected ValueCutoff in SettingsInfo_C2 should be numeric and between 0 and 1.")
}

}else{
if(is.na(as.numeric(SettingsInfo_Intra[["StatCutoff"]])) == TRUE |as.numeric(SettingsInfo_Intra[["StatCutoff"]]) > 1 | as.numeric(SettingsInfo_Intra[["StatCutoff"]]) < 0){
stop("Check input. The selected StatCutoff in SettingsInfo_Intra should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_CoRe[["StatCutoff"]])) == TRUE |as.numeric(SettingsInfo_CoRe[["StatCutoff"]]) > 1 | as.numeric(SettingsInfo_CoRe[["StatCutoff"]]) < 0){
stop("Check input. The selected StatCutoff in SettingsInfo_CoRe should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_Intra[["ValueCutoff"]])) == TRUE){
stop("Check input. The selected ValueCutoff in SettingsInfo_Intra should be numeric and between 0 and 1.")
}

if(is.na(as.numeric(SettingsInfo_CoRe[["ValueCutoff"]])) == TRUE){
stop("Check input. The selected ValueCutoff in SettingsInfo_CoRe should be numeric and between 0 and 1.")
}
}

#------------ NAs in data
if(is.null(InputData_C1)==FALSE){
if(nrow(InputData_C1[complete.cases(InputData_C1[[SettingsInfo_C1[["ValueCol"]]]], InputData_C1[[SettingsInfo_C1[["StatCol"]]]]), ]) < nrow(InputData_C1)){
warning("InputData_C1 includes NAs in ", SettingsInfo_C1[["ValueCol"]], " and/or in ", SettingsInfo_C1[["StatCol"]], ". ", nrow(InputData_C1)- nrow(InputData_C1[complete.cases(InputData_C1[[SettingsInfo_C1[["ValueCol"]]]], InputData_C1[[SettingsInfo_C1[["StatCol"]]]]), ]) ," metabolites containing NAs are removed.")
}

if(nrow(InputData_C2[complete.cases(InputData_C2[[SettingsInfo_C2[["ValueCol"]]]], InputData_C2[[SettingsInfo_C2[["StatCol"]]]]), ]) < nrow(InputData_C2)){
warning("InputData_C2 includes NAs in ", SettingsInfo_C2[["ValueCol"]], " and/or in", SettingsInfo_C2[["StatCol"]], ". ", nrow(InputData_C2)- nrow(InputData_C2[complete.cases(InputData_C2[[SettingsInfo_C2[["ValueCol"]]]], InputData_C2[[SettingsInfo_C2[["StatCol"]]]]), ]) ," metabolites containing NAs are removed.")
}
}else{
if(nrow(InputData_Intra[complete.cases(InputData_Intra[[SettingsInfo_Intra[["ValueCol"]]]], InputData_Intra[[SettingsInfo_Intra[["StatCol"]]]]), ]) < nrow(InputData_Intra)){
warning("InputData_Intra includes NAs in ", SettingsInfo_Intra[["ValueCol"]], " and/or in ", SettingsInfo_Intra[["StatCol"]], ". ", nrow(InputData_Intra)- nrow(InputData_Intra[complete.cases(InputData_Intra[[SettingsInfo_Intra[["ValueCol"]]]], InputData_Intra[[SettingsInfo_Intra[["StatCol"]]]]), ]) ," metabolites containing NAs are removed.")
}

if(nrow(InputData_CoRe[complete.cases(InputData_CoRe[[SettingsInfo_CoRe[["ValueCol"]]]], InputData_CoRe[[SettingsInfo_CoRe[["StatCol"]]]]), ]) < nrow(InputData_CoRe)){
warning("InputData_CoRe includes NAs in ", SettingsInfo_CoRe[["ValueCol"]], " and/or in ", SettingsInfo_CoRe[["StatCol"]], ". ", nrow(InputData_CoRe)- nrow(InputData_CoRe[complete.cases(InputData_CoRe[[SettingsInfo_CoRe[["ValueCol"]]]], InputData_CoRe[[SettingsInfo_CoRe[["StatCol"]]]]), ]) ," metabolites containing NAs are removed.")
}
}

#------------- BackgroundMethod
if(is.null(SettingsInfo_C1)==FALSE){
options <- c("C1|C2", "C1&C2", "C2", "C1" , "*")
if(any(options %in% BackgroundMethod) == FALSE){
stop("Check input. The selected BackgroundMethod option is not valid. Please select one of the folowwing: ",paste(options,collapse = ", "),"." )
}
}else{
options <- c("Intra|CoRe", "Intra&CoRe", "CoRe", "Intra" , "*")
if(any(options %in% BackgroundMethod) == FALSE){
stop("Check input. The selected BackgroundMethod option is not valid. Please select one of the folowwing: ",paste(options,collapse = ", "),"." )
}
}

#------------- SaveAs
SaveAs_Table_options <- c("txt","csv", "xlsx", "RData")#RData = SummarizedExperiment (?)
if(is.null(SaveAs_Table)==FALSE){
if((SaveAs_Table %in% SaveAs_Table_options == FALSE)| (is.null(SaveAs_Table)==TRUE)){
stop("Check input. The selected SaveAs_Table option is not valid. Please select one of the folowwing: ",paste(SaveAs_Table_options,collapse = ", "),"." )
}
}
}


Loading

0 comments on commit 11aa752

Please sign in to comment.