Skip to content

Commit

Permalink
Reworked outdated functions and methods.
Browse files Browse the repository at this point in the history
  • Loading branch information
alexzwanenburg committed Jan 8, 2025
1 parent 21d004a commit c0013e4
Show file tree
Hide file tree
Showing 23 changed files with 592 additions and 802 deletions.
5 changes: 4 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -204,8 +204,11 @@ Collate:
'TaskVimp.R'
'TaskVimpHyperparameters.R'
'TestDataCreators.R'
'TestFeatureInfo.R'
'TestFunctions.R'
'TrainS4Methods.R'
'TestTrain.R'
'TestTrainNovelty.R'
'TestVimp.R'
'TrimUtilities.R'
'Utilities.R'
'UtilitiesS4.R'
Expand Down
2 changes: 1 addition & 1 deletion R/FamiliarS4Generics.R
Original file line number Diff line number Diff line change
Expand Up @@ -234,7 +234,7 @@ setGeneric(".vimp", function(object, ...) standardGeneric(".vimp"))

setGeneric("promote_vimp_method", function(object, ...) standardGeneric("promote_vimp_method"))

setGeneric("prepare_vimp_object", function(data, ...) standardGeneric("prepare_vimp_object"))
setGeneric("test_create_vimp_method", function(data, ...) standardGeneric("test_create_vimp_method"))



Expand Down
56 changes: 0 additions & 56 deletions R/FeatureInfo.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,62 +2,6 @@
#' @include FamiliarS4Classes.R
NULL

create_feature_info <- function(
data,
signature = NULL,
...
) {
# This creates a list of featureInfo objects, with processing, based on data.
# This code is primarily used within unit tests.

# Reconstitute settings from the data.
settings <- extract_settings_from_data(data = data)

# Update some missing settings that can be fixed within this method.
settings$data$train_cohorts <- unique(data@data[[get_id_columns(single_column = "batch")]])

# Parse the remaining settings that are important.
settings <- do.call(
.parse_general_settings,
args = c(
list(
"settings" = settings,
"data" = data@data
),
list(...)
)
)

# Create a list of featureInfo objects.
feature_info_list <- .get_feature_info_data(
data = data@data,
file_paths = NULL,
project_id = character(),
outcome_type = data@outcome_type
)

# Extract the generic data.
feature_info_list <- feature_info_list[["generic"]]

# Add signature feature info
feature_info_list <- add_signature_info(
feature_info_list = feature_info_list,
signature = signature
)

# Perform some pre-processing (i.e. remove singular features)
feature_info_list <- .determine_preprocessing_parameters(
cl = NULL,
data = data,
feature_info_list = feature_info_list,
settings = settings,
verbose = FALSE
)

return(feature_info_list)
}



.get_feature_info_data <- function(
data,
Expand Down
14 changes: 8 additions & 6 deletions R/ParseData.R
Original file line number Diff line number Diff line change
Expand Up @@ -804,17 +804,19 @@
data_column_info = create_data_column_info(settings = settings)
)

# Add generic feature information.
generic_feature_info_task <- new("familiarTaskGenericFeatureInfo")
generic_feature_info <- .perform_task(
object = generic_feature_info_task,
data = data
)

# Set up vimp object and promote to concordance.
vimp_object <- promote_vimp_method(methods::new(
"familiarVimpMethod",
outcome_type = data@outcome_type,
outcome_info = data@outcome_info,
feature_info = .get_feature_info_data(
data = data@data,
file_paths = NULL,
project_id = character(),
outcome_type = settings$data$outcome_type
)[["generic"]],
feature_info = generic_feature_info,
vimp_method = "concordance"
))

Expand Down
59 changes: 59 additions & 0 deletions R/TestFeatureInfo.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
test_create_generic_info <- function(
data
) {
# Setup feature info task.
feature_info_task <- methods::new(
"familiarTaskGenericFeatureInfo"
)

# Feature information objects are created from the bypass dataset.
feature_info <- .perform_task(
object = feature_info_task,
data = data
)

return(feature_info)
}



test_create_feature_info <- function(
data,
signature = NULL,
...
) {
# This creates a list of featureInfo objects, with processing, based on data.
# This code is primarily used within unit tests.

# Reconstitute settings from the data.
settings <- extract_settings_from_data(data = data)

# Update some missing settings that can be fixed within this method.
settings$data$train_cohorts <- unique(data@data[[get_id_columns(single_column = "batch")]])

# Parse the remaining settings that are important.
settings <- do.call(
.parse_general_settings,
args = c(
list(
"settings" = settings,
"data" = data@data
),
list(...)
)
)

# Setup feature info task.
feature_info_task <- methods::new(
"familiarTaskFeatureInfo"
)

# Feature information objects are created from the bypass dataset.
feature_info <- .perform_task(
object = feature_info_task,
data = data,
settings = settings
)

return(feature_info)
}
16 changes: 8 additions & 8 deletions R/TestFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -2139,7 +2139,7 @@ test_all_vimp_methods <- function(
# Full dataset -----------------------------------------------------------

# Process dataset.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = full_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2250,7 +2250,7 @@ test_all_vimp_methods <- function(
# One-feature dataset ----------------------------------------------------

# Process dataset.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = one_feature_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2317,7 +2317,7 @@ test_all_vimp_methods <- function(
no_censoring_data <- test_create_good_data_without_censoring(outcome_type)

# Process dataset.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = no_censoring_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2354,7 +2354,7 @@ test_all_vimp_methods <- function(
one_censored_data <- test_create_good_data_one_censored(outcome_type)

# Process dataset.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = one_censored_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2390,7 +2390,7 @@ test_all_vimp_methods <- function(
few_censored_data <- test_create_good_data_few_censored(outcome_type)

# Process dataset.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = few_censored_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2426,7 +2426,7 @@ test_all_vimp_methods <- function(
# Fully prospective dataset ----------------------------------------------

# Set up the vimp object.
vimp_object <- prepare_vimp_object(
vimp_object <- test_create_vimp_method(
data = full_data,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
Expand Down Expand Up @@ -2553,7 +2553,7 @@ test_all_vimp_methods_parallel <- function(
"1" = full_data,
"2" = full_data
),
prepare_vimp_object,
test_create_vimp_method,
vimp_method = vimp_method,
vimp_method_parameter_list = hyperparameters,
outcome_type = outcome_type,
Expand Down Expand Up @@ -5253,7 +5253,7 @@ test_not_deprecated <- function(x, deprecation_string = c("deprec", "replac")) {
}

# Create feature info list.
feature_info_list <- create_feature_info(
feature_info_list <- test_create_feature_info(
data = data,
vimp_method = vimp_method,
learner = learner,
Expand Down
Loading

0 comments on commit c0013e4

Please sign in to comment.