Skip to content

Commit

Permalink
Working in place enum declarations.
Browse files Browse the repository at this point in the history
  • Loading branch information
dereckmezquita committed Jul 29, 2024
1 parent f4b9c0e commit 9ad19c0
Show file tree
Hide file tree
Showing 2 changed files with 52 additions and 9 deletions.
42 changes: 38 additions & 4 deletions R/type.frame.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,21 +53,55 @@ type.frame <- function(
) {
on_violation <- match.arg(on_violation)

# Process in-place enum declarations
for (name in names(col_types)) {
if (inherits(col_types[[name]], "enum_generator")) {
enum_generator <- col_types[[name]]
col_types[[name]] <- list(
type = "enum",
validator = function(x) {
if (is.character(x)) {
return(enum_generator(x))
} else if (inherits(x, "enum")) {
return(x)
} else {
stop(sprintf("Invalid value for enum '%s'. Must be a character or enum object.", name))
}
},
values = attr(enum_generator, "values")
)
}
}

creator <- function(...) {
df <- frame(...)
errors <- list()

# Validate column types
# Validate column types and convert enum values
for (col_name in names(col_types)) {
if (!(col_name %in% names(df))) {
errors <- c(errors, sprintf("Required column '%s' is missing", col_name))
} else {
col_data <- df[[col_name]]
col_type <- col_types[[col_name]]

error <- validate_property(col_name, col_data, col_type)
if (!is.null(error)) {
errors <- c(errors, error)
# Handle enum conversion
if (is.list(col_type) && col_type$type == "enum") {
df[[col_name]] <- sapply(col_data, function(x) {
tryCatch(
col_type$validator(x),
error = function(e) {
errors <<- c(errors, sprintf("Invalid enum value for column '%s': %s", col_name, x))
return(x) # Return original value to allow further processing
}
)
})
} else {
# For non-enum columns, use the original type
error <- validate_property(col_name, df[[col_name]], col_type)
if (!is.null(error)) {
errors <- c(errors, error)
}
}
}
}
Expand Down
19 changes: 14 additions & 5 deletions R/validate_property.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,20 @@
#' @return NULL if the validation passes, otherwise an error message.
#'
validate_property <- function(name, value, validator) {
if (is.list(validator) && !is.function(validator)) {
if (is.list(validator) && validator$type == "enum") {
# Handle enum validation
if (inherits(value, "enum")) {
if (!value$value %in% validator$values) {
return(sprintf("Property '%s' must be one of the enum values: %s", name, paste(validator$values, collapse = ", ")))
}
} else if (is.character(value)) {
if (!value %in% validator$values) {
return(sprintf("Property '%s' must be one of the enum values: %s", name, paste(validator$values, collapse = ", ")))
}
} else {
return(sprintf("Property '%s' must be an enum object or a valid enum value", name))
}
} else if (is.list(validator) && !is.function(validator)) {
# Multiple allowed types
for (v in validator) {
error <- validate_property(name, value, v)
Expand All @@ -20,10 +33,6 @@ validate_property <- function(name, value, validator) {
if (!inherits(value, "interface_object") || !identical(attr(value, "properties"), attr(validator, "properties"))) {
return(sprintf("Property '%s' must be an object implementing the specified interface", name))
}
} else if (inherits(validator, "enum_generator")) {
if (!inherits(value, "enum") || !value$value %in% attr(validator, "values")) {
return(sprintf("Property '%s' must be one of the enum values: %s", name, paste(attr(validator, "values"), collapse = ", ")))
}
} else if (is.function(validator)) {
if (identical(validator, character)) {
if (!is.character(value)) {
Expand Down

0 comments on commit 9ad19c0

Please sign in to comment.