From ce99b599f8249e8740a059803ae6e08a9f6651bf Mon Sep 17 00:00:00 2001 From: aheinri5 <Anna@netzkritzler.de> Date: Thu, 28 Jan 2021 18:35:32 +0100 Subject: [PATCH] [base] closes #11 , adding .prj components now via OGS() --- R/export_prj.R | 2 +- R/generate_benchmark_script.R | 13 +- R/ogs6.R | 299 +++++------------- R/read_in_prj.R | 2 +- R/read_in_utils.R | 5 +- R/utils.R | 24 +- man/OGS6.Rd | 299 ++---------------- ...j_tag_info.Rd => prj_top_level_classes.Rd} | 11 +- man/prj_top_level_tags.Rd | 14 + .../testthat/test-generate_benchmark_script.R | 4 +- tests/testthat/test-ogs6.R | 6 +- tests/testthat/test-ogs6_ensemble.R | 3 +- tests/testthat/test-utils.R | 4 +- vignettes/dev_workflow_vignette.Rmd | 3 + vignettes/user_workflow_vignette.Rmd | 6 +- 15 files changed, 180 insertions(+), 515 deletions(-) rename man/{get_prj_tag_info.Rd => prj_top_level_classes.Rd} (65%) create mode 100644 man/prj_top_level_tags.Rd diff --git a/R/export_prj.R b/R/export_prj.R index a6d2609..078af44 100644 --- a/R/export_prj.R +++ b/R/export_prj.R @@ -29,7 +29,7 @@ export_prj <- function(ogs6_obj) { xml2::as_xml_document(meshes_node)) #Get implemented classes - prj_components <- get_prj_tag_info() + prj_components <- prj_top_level_classes() # Include file reference if(names(ogs6_obj$processes)[[1]] == "include"){ diff --git a/R/generate_benchmark_script.R b/R/generate_benchmark_script.R index c3ba868..4dc8d06 100644 --- a/R/generate_benchmark_script.R +++ b/R/generate_benchmark_script.R @@ -177,7 +177,7 @@ generate_benchmark_script <- function(prj_path, read_in_vtu, read_in_gml = FALSE) - prj_components = get_prj_tag_info() + prj_components = prj_top_level_classes() sim_name <- tools::file_path_sans_ext(basename(prj_path)) @@ -355,13 +355,11 @@ construct_add_call <- function(object, nested_call = FALSE) { ret_str <- paste0(class_name, init_prefix, "(", content_str, ")") - #If call isn't nested, it has a OGS6$add_* function + #If call isn't nested, it can be added if(!nested_call){ - ret_str <- paste0("ogs6_obj$add_", tag_name, - "(", ret_str, ")\n") + ret_str <- paste0("ogs6_obj$add(", ret_str, ")\n") } - ret_str <- delete_nulls_from_str(ret_str) ret_str <- delete_keywords_from_str(ret_str) ret_str <- delete_empty_from_str(ret_str) @@ -376,11 +374,8 @@ construct_add_call <- function(object, nested_call = FALSE) { return(invisible(ret_str)) } - #Positioning is important here - r2ogs6 objects are built on top of lists! - #If is.list is checked before class, results will not be as intended! - #For lists we need to use recursion - if(is.list(object)){ + if(class(object) == "list"){ element_strs <- lapply(object, function(x){construct_add_call(x, TRUE)}) diff --git a/R/ogs6.R b/R/ogs6.R index cf6bb70..73fc732 100644 --- a/R/ogs6.R +++ b/R/ogs6.R @@ -32,60 +32,20 @@ OGS6 <- R6::R6Class("OGS6", }, - #===== ADDING COMPONENTS ===== + #===== Adding components ===== #'@description - #'Adds a simulation component (WIP) - #'@param x An object of any class listed in addable_components(). If `x` is - #' not of a proprietary `r2ogs6` class, it must be a string referencing a - #' file. E.g. If you're adding a `python_script`, call - #' `your_ogs6_obj$add("some_script.py")`. If you're adding a `geometry` or - #' `mesh` reference, if `...` is not defined, they will be read in. To - #' disable, define `read_in` as `FALSE`. + #'Adds a .prj simulation component + #'@param x An object of any .prj `r2ogs6` class add = function(x){ - # Assert that class name is in implemented classes for OGS6 - ogs6_components <- get_prj_tag_info() + # Assert that class name is in implemented .prj classes for OGS6 + ogs6_prj_classes <- prj_top_level_classes() + assertthat::assert_that(class(x) %in% ogs6_prj_classes) - x_class_name <- "" - x_of_r2ogs6_class <- FALSE - - if(any(grepl("r2ogs6", class(x), fixed = TRUE)) || - any(grepl("OGS6", class(x), fixed = TRUE))){ - - x_class_name <- grep("r2ogs6", class(x), value = TRUE) - - if(length(x_class_name) == 0){ - x_class_name <- grep("OGS6", class(x), value = TRUE) - } - - assertthat::assert_that(x_class_name %in% ogs6_components) - x_of_r2ogs6_class <- TRUE - } - - # Get name of corresponding OGS6 parameter - if(x_of_r2ogs6_class){ - component_name <- - names(ogs6_components)[ogs6_components == x_class_name] - }else{ - assertthat::assert_that(assertthat::is.string(x)) - - switch (tools::file_ext(x), - gml = { - }, - - vtu = { - }, - - py = { - component_name <- "python_script" - }, - - stop(paste("When adding a file reference to your OGS6 object, it", - "must be a .gml, .vtu or .py file."), call. = FALSE) - ) - } + # Get name of corresponding OGS6 component + component_name <- names(ogs6_prj_classes)[ogs6_prj_classes == class(x)] component_class <- eval(parse(text = paste0("class(self$", component_name, ")"))) @@ -100,7 +60,7 @@ OGS6 <- R6::R6Class("OGS6", # If class has `name` variable, make it accessable by name if(component_class == "list" && - "name" %in% names(as.list(formals(x_class_name)))){ + "name" %in% names(as.list(formals(class(x))))){ name_call <- paste0("names(self$", component_name, ")[[length(self$", component_name, ")]] <- x$name") @@ -149,119 +109,8 @@ OGS6 <- R6::R6Class("OGS6", } }, - #'@description - #'Adds a python script - #'@param python_script string: File name of python script - add_python_script = function(python_script){ - self$python_script <- python_script - }, - #'@description - #'Adds a r2ogs6_search_length_algorithm object - #'@param search_length_algorithm r2ogs6_search_length_algorithm - add_search_length_algorithm = function(search_length_algorithm){ - self$search_length_algorithm <- search_length_algorithm - }, - - #'@description - #'Adds a r2ogs6_process object - #'@param process r2ogs6_process - add_process = function(process){ - self$processes <- c(self$processes, - list(process)) - - names(self$processes)[[length(self$processes)]] <- process$name - }, - - #'@description - #'Adds a r2ogs6_time_loop object - #'@param time_loop r2ogs6_time_loop - add_time_loop = function(time_loop){ - self$time_loop <- time_loop - }, - - #'@description - #'Adds a r2ogs6_local_coordinate_system object - #'@param local_coordinate_system r2ogs6_local_coordinate_system - add_local_coordinate_system = function(local_coordinate_system){ - self$local_coordinate_system <- local_coordinate_system - }, - - #'@description - #'Adds a r2ogs6_medium object - #'@param medium r2ogs6_medium - add_medium = function(medium){ - self$media <- c(self$media, - list(medium)) - }, - - #'@description - #'Adds a r2ogs6_parameter object - #'@param parameter r2ogs6_parameter - add_parameter = function(parameter){ - self$parameters <- c(self$parameters, - list(parameter)) - - names(self$parameters)[[length(self$parameters)]] <- parameter$name - }, - - #'@description - #'Adds a r2ogs6_curve object - #'@param curve r2ogs6_curve - add_curve = function(curve){ - self$curves <- c(self$curves, - list(curve)) - }, - - #'@description - #'Adds a r2ogs6_process_variable object - #'@param process_variable r2ogs6_process_variable - add_process_variable = function(process_variable){ - self$process_variables <- c(self$process_variables, - list(process_variable)) - - names(self$process_variables)[[length(self$process_variables)]] <- - process_variable$name - }, - - #'@description - #'Adds a r2ogs6_nonlinear_solver object - #'@param nonlinear_solver r2ogs6_nonlinear_solver - add_nonlinear_solver = function(nonlinear_solver){ - self$nonlinear_solvers <- c(self$nonlinear_solvers, - list(nonlinear_solver)) - - names(self$nonlinear_solvers)[[length(self$nonlinear_solvers)]] <- - nonlinear_solver$name - }, - - #'@description - #'Adds a r2ogs6_linear_solver object - #'@param linear_solver r2ogs6_linear_solver - add_linear_solver = function(linear_solver){ - self$linear_solvers <- c(self$linear_solvers, - list(linear_solver)) - - names(self$linear_solvers)[[length(self$linear_solvers)]] <- - linear_solver$name - }, - - #'@description - #'Adds a r2ogs6_vtkdiff object - #'@param vtkdiff r2ogs6_vtkdiff - add_vtkdiff = function(vtkdiff){ - self$test_definition <- c(self$test_definition, list(vtkdiff)) - }, - - #'@description - #'Adds a r2ogs6_insitu object - #'@param insitu r2ogs6_insitu - add_insitu = function(insitu){ - self$insitu <- insitu - }, - - - #===== UTILITY FUNCTIONS ===== + #===== Utility ===== #'@description @@ -274,26 +123,18 @@ OGS6 <- R6::R6Class("OGS6", flag <- TRUE status_strs <- character() - - prj_reduxml <- system.file("extdata/xml_redux/", "prj_redu.xml", - package = "r2ogs6") - - xml_doc <- xml2::read_xml(prj_reduxml) - tag_names <- lapply(xml2::xml_children(xml_doc), xml2::xml_name) + tag_names <- lapply(prj_top_level_tags(), `[[`, 1) + required <- lapply(prj_top_level_tags(), `[[`, 2) for(i in seq_len(length(tag_names))){ - prj_node <- xml2::xml_find_first(xml_doc, - paste0("/OpenGeoSysProject/", - tag_names[[i]])) - - is_optional <- (xml2::xml_attrs(prj_node)[["required"]] == "FALSE") + is_required <- required[[i]] prj_obj_call <- paste0("private$.", tag_names[[i]]) prj_obj <- eval(parse(text = prj_obj_call)) if(length(prj_obj) == 0){ - if(!is_optional){ + if(is_required){ status_str <- crayon::red("\u2717 ") flag <- FALSE }else{ @@ -304,11 +145,11 @@ OGS6 <- R6::R6Class("OGS6", } status_str <- paste0(status_str, - "OGS6$", + "'", tag_names[[i]], ifelse(!class(prj_obj) == "list", - " is defined", - " has at least one element")) + "' is defined", + "' has at least one element")) status_strs <- c(status_strs, status_str) } @@ -343,14 +184,14 @@ OGS6 <- R6::R6Class("OGS6", #'Clears components from the OGS6 object #'@param which character: The names of the components (all by default). #' If you want to delete only some components, run - #' names(get_prj_tag_info()) for the available options. + #' names(prj_top_level_classes()) for the available options. clear = function(which){ if(missing(which)){ - which <- names(get_prj_tag_info()) + which <- names(prj_top_level_classes()) } - valid_input = names(get_prj_tag_info()) + valid_input = names(prj_top_level_classes()) null_it <- c("geometry", "time_loop") @@ -377,13 +218,13 @@ OGS6 <- R6::R6Class("OGS6", ), - #===== ACTIVE FIELDS ===== + #===== Active fields ===== active = list( #'@field sim_name - #'Access to private parameter '.sim_name' + #'Simulation name. `value` must be string sim_name = function(value) { if(missing(value)) { private$.sim_name @@ -394,13 +235,13 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field sim_id - #'Getter for OGS6 private parameter '.sim_id' + #'Simulation ID. read-only sim_id = function() { private$.sim_id }, #'@field sim_path - #'Access to private parameter '.sim_path' + #'Simulation path. `value` must be string sim_path = function(value) { if(missing(value)) { private$.sim_path @@ -410,7 +251,7 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field logfile - #'Access to private parameter '.logfile' + #'Logfile path. `value` must be string logfile = function(value) { if(missing(value)) { private$.logfile @@ -421,13 +262,13 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field gml - #'Getter for OGS6 private parameter '.gml' + #'.gml. read-only gml = function() { private$.gml }, #'@field geometry - #'Access to private parameter '.geometry' + #'.prj `geometry` tag. `value` must be string geometry = function(value) { if(missing(value)) { private$.geometry @@ -438,7 +279,7 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field meshes - #'Access to private parameter '.meshes' + #'.prj `meshes` tag. `value` must be list of strings meshes = function(value) { if(missing(value)) { private$.meshes @@ -452,19 +293,19 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field vtus - #'Access to private parameter '.vtus' + #'.vtus. `value` must be list of `OGS_vtu` objects vtus = function(value) { if(missing(value)) { private$.vtus }else{ is_wrapper_list(value, - get_prj_tag_info()[["vtus"]]) + prj_top_level_classes()[["vtus"]]) private$.vtus <- value } }, #'@field python_script - #'Access to private parameter '.python_script' + #'.prj `python_script` tag. `value` must be string python_script = function(value) { if(missing(value)) { private$.python_script @@ -475,30 +316,31 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field search_length_algorithm - #'Access to private parameter '.search_length_algorithm' + #'.prj `search_length_algorithm` tag. `value` must be + #' `r2ogs6_search_length_algorithm` object search_length_algorithm = function(value) { if(missing(value)) { private$.search_length_algorithm }else{ assertthat::assert_that( - get_prj_tag_info()[["search_length_algorithm"]] %in% + prj_top_level_classes()[["search_length_algorithm"]] %in% class(value)) private$.search_length_algorithm <- value } }, #'@field processes - #'Access to private parameter '.processes' + #'.prj `processes` tag. `value` must be list of `r2ogs6_process` objects processes = function(value) { if(missing(value)) { private$.processes }else{ # If there already is a process element if(length(private$.processes) > 0){ - if(get_prj_tag_info()[["processes"]] %in% + if(prj_top_level_classes()[["processes"]] %in% class(private$.processes[[1]])){ is_wrapper_list(value, - get_prj_tag_info()[["processes"]]) + prj_top_level_classes()[["processes"]]) }else{ assertthat::assert_that(assertthat::is.string(value)) value <- list(include = c(file = value)) @@ -509,7 +351,7 @@ OGS6 <- R6::R6Class("OGS6", value <- list(include = c(file = value)) }else{ is_wrapper_list(value, - get_prj_tag_info()[["processes"]]) + prj_top_level_classes()[["processes"]]) } } @@ -518,132 +360,152 @@ OGS6 <- R6::R6Class("OGS6", }, #'@field time_loop - #'Access to private parameter '.time_loop' + #'.prj `time_loop` tag. `value` must be `r2ogs6_time_loop` object time_loop = function(value) { if(missing(value)) { private$.time_loop }else{ assertthat::assert_that( - get_prj_tag_info()[["time_loop"]] %in% + prj_top_level_classes()[["time_loop"]] %in% class(value)) private$.time_loop <- value } }, #'@field local_coordinate_system - #'Access to private parameter '.local_coordinate_system' + #'.prj `local_coordinate_system` tag. `value` must be + #' `r2ogs6_local_coordinate_system` object local_coordinate_system = function(value) { if(missing(value)) { private$.local_coordinate_system }else{ assertthat::assert_that( - get_prj_tag_info()[["local_coordinate_system"]] %in% + prj_top_level_classes()[["local_coordinate_system"]] %in% class(value)) private$.local_coordinate_system <- value } }, #'@field media - #'Access to private parameter '.media' + #'.prj `media` tag. `value` must be list of `r2ogs6_medium` objects media = function(value) { if(missing(value)) { private$.media }else{ is_wrapper_list(value, - get_prj_tag_info()[["media"]]) + prj_top_level_classes()[["media"]]) private$.media <- value } }, #'@field parameters - #'Access to private parameter '.parameters' + #'.prj `parameters` tag. `value` must be list of `r2ogs6_parameter` + #' objects parameters = function(value) { if(missing(value)) { private$.parameters }else{ is_wrapper_list(value, - get_prj_tag_info()[["parameters"]]) + prj_top_level_classes()[["parameters"]]) private$.parameters <- value } }, + #'@field chemical_system + #'.prj `chemical_system` tag. `value` must be `r2ogs6_chemical_system` + #' object + chemical_system = function(value) { + if(missing(value)) { + private$.chemical_system + }else{ + assertthat::assert_that( + prj_top_level_classes()[["chemical_system"]] %in% + class(value)) + private$.chemical_system <- value + } + }, + #'@field curves - #'Access to private parameter '.curves' + #'.prj `curves` tag. `value` must be list of `r2ogs6_curve` objects curves = function(value) { if(missing(value)) { private$.curves }else{ is_wrapper_list(value, - get_prj_tag_info()[["curves"]]) + prj_top_level_classes()[["curves"]]) private$.curves <- value } }, #'@field process_variables - #'Access to private parameter '.process_variables' + #'.prj `process_variables` tag. `value` must be list of + #' `r2ogs6_process_variable` objects process_variables = function(value) { if(missing(value)) { private$.process_variables }else{ is_wrapper_list( value, - get_prj_tag_info()[["process_variables"]]) + prj_top_level_classes()[["process_variables"]]) private$.process_variables <- value } }, #'@field nonlinear_solvers - #'Access to private parameter '.nonlinear_solvers' + #'.prj `nonlinear_solvers` tag. `value` must be list of + #' `r2ogs6_nonlinear_solver` objects nonlinear_solvers = function(value) { if(missing(value)) { private$.nonlinear_solvers }else{ is_wrapper_list( value, - get_prj_tag_info()[["nonlinear_solvers"]]) + prj_top_level_classes()[["nonlinear_solvers"]]) private$.nonlinear_solvers <- value } }, #'@field linear_solvers - #'Access to private parameter '.linear_solvers' + #'.prj `linear_solvers` tag. `value` must be list of + #' `r2ogs6_linear_solver` objects linear_solvers = function(value) { if(missing(value)) { private$.linear_solvers }else{ is_wrapper_list(value, - get_prj_tag_info()[["linear_solvers"]]) + prj_top_level_classes()[["linear_solvers"]]) private$.linear_solvers <- value } }, #'@field test_definition - #'Access to private parameter '.test_definition' + #'.prj `test_definition` tag. `value` must be list of `r2ogs6_vtkdiff` + #' objects test_definition = function(value) { if(missing(value)) { private$.test_definition }else{ is_wrapper_list(value, - get_prj_tag_info()[["test_definition"]]) + prj_top_level_classes()[["test_definition"]]) private$.test_definition <- value } }, #'@field insitu - #'Access to private parameter '.insitu' + #'.prj `insitu` tag. `value` must be `r2ogs6_insitu` object insitu = function(value) { if(missing(value)) { private$.insitu }else{ assertthat::assert_that( - get_prj_tag_info()[["insitu"]] %in% + prj_top_level_classes()[["insitu"]] %in% class(value)) private$.insitu <- value } }, #'@field pvd - #'Access to private parameter '.pvd' + #'.pvd. `value` must be `OGS6_pvd` object pvd = function(value) { if(missing(value)) { private$.pvd @@ -654,6 +516,8 @@ OGS6 <- R6::R6Class("OGS6", } ), + #===== Private parameters ===== + private = list( # general parameters .sim_name = NULL, @@ -683,6 +547,7 @@ OGS6 <- R6::R6Class("OGS6", .local_coordinate_system = NULL, .media = list(), .parameters = list(), + .chemical_system = NULL, .curves = list(), .process_variables = list(), .nonlinear_solvers = list(), diff --git a/R/read_in_prj.R b/R/read_in_prj.R index 1920da4..d0dd5f8 100644 --- a/R/read_in_prj.R +++ b/R/read_in_prj.R @@ -61,7 +61,7 @@ read_in_prj <- function(ogs6_obj, read_in_vtu = read_in_vtu) } - prj_components <- get_prj_tag_info() + prj_components <- prj_top_level_classes() # Include file reference processes_include_node <- diff --git a/R/read_in_utils.R b/R/read_in_utils.R index a251b07..9370fa4 100644 --- a/R/read_in_utils.R +++ b/R/read_in_utils.R @@ -56,9 +56,6 @@ read_in <- function(ogs6_obj, r2ogs6_obj <- NULL - #Code to be parsed when r2ogs6_obj has been defined - add_call <- paste0("ogs6_obj$add_", child_name, "(r2ogs6_obj)") - #Parse all children for (i in seq_len(length(nodes))) { @@ -66,7 +63,7 @@ read_in <- function(ogs6_obj, xpath) #Add r2ogs6_obj with code snippet - eval(parse(text = add_call)) + eval(parse(text = "ogs6_obj$add(r2ogs6_obj)")) } return(invisible(r2ogs6_obj)) diff --git a/R/utils.R b/R/utils.R index 44e0ee0..6403f8f 100644 --- a/R/utils.R +++ b/R/utils.R @@ -56,10 +56,30 @@ get_tag_from_xpath <- function(xpath){ } -#'get_prj_tag_info +#'prj_top_level_tags +#'@description Gets top level .prj tags along with info if they are required. +#'@return list: List of lists. +prj_top_level_tags <- function(){ + + prj_reduxml <- system.file("extdata/xml_redux/", "prj_redu.xml", + package = "r2ogs6") + + xml_doc <- xml2::read_xml(prj_reduxml) + + prj_tag_info <- lapply(xml2::xml_children(xml_doc), function(x){ + list(tag_name = xml2::xml_name(x), + is_required = as.logical(xml2::xml_attrs(x)[["required"]])) + }) + + return(prj_tag_info) +} + + +#'prj_top_level_classes #'@description Returns named character vector of `OGS6` top level .prj tags #' (names) represented by r2ogs6 classes along with their class names (values). -get_prj_tag_info <- function(){ +#'@return character +prj_top_level_classes <- function(){ xpaths_for_classes <- xpaths_for_classes diff --git a/man/OGS6.Rd b/man/OGS6.Rd index 3ccd5f7..971ebd0 100644 --- a/man/OGS6.Rd +++ b/man/OGS6.Rd @@ -9,49 +9,59 @@ Constructor for the OGS6 base class \section{Active bindings}{ \if{html}{\out{<div class="r6-active-bindings">}} \describe{ -\item{\code{sim_name}}{Access to private parameter '.sim_name'} +\item{\code{sim_name}}{Simulation name. `value` must be string} -\item{\code{sim_id}}{Getter for OGS6 private parameter '.sim_id'} +\item{\code{sim_id}}{Simulation ID. read-only} -\item{\code{sim_path}}{Access to private parameter '.sim_path'} +\item{\code{sim_path}}{Simulation path. `value` must be string} -\item{\code{logfile}}{Access to private parameter '.logfile'} +\item{\code{logfile}}{Logfile path. `value` must be string} -\item{\code{gml}}{Getter for OGS6 private parameter '.gml'} +\item{\code{gml}}{.gml. read-only} -\item{\code{geometry}}{Access to private parameter '.geometry'} +\item{\code{geometry}}{.prj `geometry` tag. `value` must be string} -\item{\code{meshes}}{Access to private parameter '.meshes'} +\item{\code{meshes}}{.prj `meshes` tag. `value` must be list of strings} -\item{\code{vtus}}{Access to private parameter '.vtus'} +\item{\code{vtus}}{.vtus. `value` must be list of `OGS_vtu` objects} -\item{\code{python_script}}{Access to private parameter '.python_script'} +\item{\code{python_script}}{.prj `python_script` tag. `value` must be string} -\item{\code{search_length_algorithm}}{Access to private parameter '.search_length_algorithm'} +\item{\code{search_length_algorithm}}{.prj `search_length_algorithm` tag. `value` must be +`r2ogs6_search_length_algorithm` object} -\item{\code{processes}}{Access to private parameter '.processes'} +\item{\code{processes}}{.prj `processes` tag. `value` must be list of `r2ogs6_process` objects} -\item{\code{time_loop}}{Access to private parameter '.time_loop'} +\item{\code{time_loop}}{.prj `time_loop` tag. `value` must be `r2ogs6_time_loop` object} -\item{\code{local_coordinate_system}}{Access to private parameter '.local_coordinate_system'} +\item{\code{local_coordinate_system}}{.prj `local_coordinate_system` tag. `value` must be +`r2ogs6_local_coordinate_system` object} -\item{\code{media}}{Access to private parameter '.media'} +\item{\code{media}}{.prj `media` tag. `value` must be list of `r2ogs6_medium` objects} -\item{\code{parameters}}{Access to private parameter '.parameters'} +\item{\code{parameters}}{.prj `parameters` tag. `value` must be list of `r2ogs6_parameter` +objects} -\item{\code{curves}}{Access to private parameter '.curves'} +\item{\code{chemical_system}}{.prj `chemical_system` tag. `value` must be `r2ogs6_chemical_system` +object} -\item{\code{process_variables}}{Access to private parameter '.process_variables'} +\item{\code{curves}}{.prj `curves` tag. `value` must be list of `r2ogs6_curve` objects} -\item{\code{nonlinear_solvers}}{Access to private parameter '.nonlinear_solvers'} +\item{\code{process_variables}}{.prj `process_variables` tag. `value` must be list of +`r2ogs6_process_variable` objects} -\item{\code{linear_solvers}}{Access to private parameter '.linear_solvers'} +\item{\code{nonlinear_solvers}}{.prj `nonlinear_solvers` tag. `value` must be list of +`r2ogs6_nonlinear_solver` objects} -\item{\code{test_definition}}{Access to private parameter '.test_definition'} +\item{\code{linear_solvers}}{.prj `linear_solvers` tag. `value` must be list of +`r2ogs6_linear_solver` objects} -\item{\code{insitu}}{Access to private parameter '.insitu'} +\item{\code{test_definition}}{.prj `test_definition` tag. `value` must be list of `r2ogs6_vtkdiff` +objects} -\item{\code{pvd}}{Access to private parameter '.pvd'} +\item{\code{insitu}}{.prj `insitu` tag. `value` must be `r2ogs6_insitu` object} + +\item{\code{pvd}}{.pvd. `value` must be `OGS6_pvd` object} } \if{html}{\out{</div>}} } @@ -62,19 +72,6 @@ Constructor for the OGS6 base class \item \href{#method-add}{\code{OGS6$add()}} \item \href{#method-add_gml}{\code{OGS6$add_gml()}} \item \href{#method-add_vtu}{\code{OGS6$add_vtu()}} -\item \href{#method-add_python_script}{\code{OGS6$add_python_script()}} -\item \href{#method-add_search_length_algorithm}{\code{OGS6$add_search_length_algorithm()}} -\item \href{#method-add_process}{\code{OGS6$add_process()}} -\item \href{#method-add_time_loop}{\code{OGS6$add_time_loop()}} -\item \href{#method-add_local_coordinate_system}{\code{OGS6$add_local_coordinate_system()}} -\item \href{#method-add_medium}{\code{OGS6$add_medium()}} -\item \href{#method-add_parameter}{\code{OGS6$add_parameter()}} -\item \href{#method-add_curve}{\code{OGS6$add_curve()}} -\item \href{#method-add_process_variable}{\code{OGS6$add_process_variable()}} -\item \href{#method-add_nonlinear_solver}{\code{OGS6$add_nonlinear_solver()}} -\item \href{#method-add_linear_solver}{\code{OGS6$add_linear_solver()}} -\item \href{#method-add_vtkdiff}{\code{OGS6$add_vtkdiff()}} -\item \href{#method-add_insitu}{\code{OGS6$add_insitu()}} \item \href{#method-get_status}{\code{OGS6$get_status()}} \item \href{#method-print_log}{\code{OGS6$print_log()}} \item \href{#method-clear}{\code{OGS6$clear()}} @@ -107,7 +104,7 @@ saved} \if{html}{\out{<a id="method-add"></a>}} \if{latex}{\out{\hypertarget{method-add}{}}} \subsection{Method \code{add()}}{ -Adds a simulation component (WIP) +Adds a .prj simulation component \subsection{Usage}{ \if{html}{\out{<div class="r">}}\preformatted{OGS6$add(x)}\if{html}{\out{</div>}} } @@ -115,12 +112,7 @@ Adds a simulation component (WIP) \subsection{Arguments}{ \if{html}{\out{<div class="arguments">}} \describe{ -\item{\code{x}}{An object of any class listed in addable_components(). If `x` is -not of a proprietary `r2ogs6` class, it must be a string referencing a -file. E.g. If you're adding a `python_script`, call -`your_ogs6_obj$add("some_script.py")`. If you're adding a `geometry` or -`mesh` reference, if `...` is not defined, they will be read in. To -disable, define `read_in` as `FALSE`.} +\item{\code{x}}{An object of any .prj `r2ogs6` class} } \if{html}{\out{</div>}} } @@ -164,227 +156,6 @@ read in too?} } } \if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_python_script"></a>}} -\if{latex}{\out{\hypertarget{method-add_python_script}{}}} -\subsection{Method \code{add_python_script()}}{ -Adds a python script -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_python_script(python_script)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{python_script}}{string: File name of python script} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_search_length_algorithm"></a>}} -\if{latex}{\out{\hypertarget{method-add_search_length_algorithm}{}}} -\subsection{Method \code{add_search_length_algorithm()}}{ -Adds a r2ogs6_search_length_algorithm object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_search_length_algorithm(search_length_algorithm)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{search_length_algorithm}}{r2ogs6_search_length_algorithm} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_process"></a>}} -\if{latex}{\out{\hypertarget{method-add_process}{}}} -\subsection{Method \code{add_process()}}{ -Adds a r2ogs6_process object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_process(process)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{process}}{r2ogs6_process} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_time_loop"></a>}} -\if{latex}{\out{\hypertarget{method-add_time_loop}{}}} -\subsection{Method \code{add_time_loop()}}{ -Adds a r2ogs6_time_loop object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_time_loop(time_loop)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{time_loop}}{r2ogs6_time_loop} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_local_coordinate_system"></a>}} -\if{latex}{\out{\hypertarget{method-add_local_coordinate_system}{}}} -\subsection{Method \code{add_local_coordinate_system()}}{ -Adds a r2ogs6_local_coordinate_system object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_local_coordinate_system(local_coordinate_system)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{local_coordinate_system}}{r2ogs6_local_coordinate_system} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_medium"></a>}} -\if{latex}{\out{\hypertarget{method-add_medium}{}}} -\subsection{Method \code{add_medium()}}{ -Adds a r2ogs6_medium object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_medium(medium)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{medium}}{r2ogs6_medium} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_parameter"></a>}} -\if{latex}{\out{\hypertarget{method-add_parameter}{}}} -\subsection{Method \code{add_parameter()}}{ -Adds a r2ogs6_parameter object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_parameter(parameter)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{parameter}}{r2ogs6_parameter} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_curve"></a>}} -\if{latex}{\out{\hypertarget{method-add_curve}{}}} -\subsection{Method \code{add_curve()}}{ -Adds a r2ogs6_curve object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_curve(curve)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{curve}}{r2ogs6_curve} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_process_variable"></a>}} -\if{latex}{\out{\hypertarget{method-add_process_variable}{}}} -\subsection{Method \code{add_process_variable()}}{ -Adds a r2ogs6_process_variable object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_process_variable(process_variable)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{process_variable}}{r2ogs6_process_variable} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_nonlinear_solver"></a>}} -\if{latex}{\out{\hypertarget{method-add_nonlinear_solver}{}}} -\subsection{Method \code{add_nonlinear_solver()}}{ -Adds a r2ogs6_nonlinear_solver object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_nonlinear_solver(nonlinear_solver)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{nonlinear_solver}}{r2ogs6_nonlinear_solver} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_linear_solver"></a>}} -\if{latex}{\out{\hypertarget{method-add_linear_solver}{}}} -\subsection{Method \code{add_linear_solver()}}{ -Adds a r2ogs6_linear_solver object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_linear_solver(linear_solver)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{linear_solver}}{r2ogs6_linear_solver} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_vtkdiff"></a>}} -\if{latex}{\out{\hypertarget{method-add_vtkdiff}{}}} -\subsection{Method \code{add_vtkdiff()}}{ -Adds a r2ogs6_vtkdiff object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_vtkdiff(vtkdiff)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{vtkdiff}}{r2ogs6_vtkdiff} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-add_insitu"></a>}} -\if{latex}{\out{\hypertarget{method-add_insitu}{}}} -\subsection{Method \code{add_insitu()}}{ -Adds a r2ogs6_insitu object -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{OGS6$add_insitu(insitu)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{insitu}}{r2ogs6_insitu} -} -\if{html}{\out{</div>}} -} -} -\if{html}{\out{<hr>}} \if{html}{\out{<a id="method-get_status"></a>}} \if{latex}{\out{\hypertarget{method-get_status}{}}} \subsection{Method \code{get_status()}}{ @@ -427,7 +198,7 @@ Clears components from the OGS6 object \describe{ \item{\code{which}}{character: The names of the components (all by default). If you want to delete only some components, run -names(get_prj_tag_info()) for the available options.} +names(prj_top_level_classes()) for the available options.} } \if{html}{\out{</div>}} } diff --git a/man/get_prj_tag_info.Rd b/man/prj_top_level_classes.Rd similarity index 65% rename from man/get_prj_tag_info.Rd rename to man/prj_top_level_classes.Rd index e7ac279..8906060 100644 --- a/man/get_prj_tag_info.Rd +++ b/man/prj_top_level_classes.Rd @@ -1,10 +1,13 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/utils.R -\name{get_prj_tag_info} -\alias{get_prj_tag_info} -\title{get_prj_tag_info} +\name{prj_top_level_classes} +\alias{prj_top_level_classes} +\title{prj_top_level_classes} \usage{ -get_prj_tag_info() +prj_top_level_classes() +} +\value{ +character } \description{ Returns named character vector of `OGS6` top level .prj tags diff --git a/man/prj_top_level_tags.Rd b/man/prj_top_level_tags.Rd new file mode 100644 index 0000000..dabe500 --- /dev/null +++ b/man/prj_top_level_tags.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{prj_top_level_tags} +\alias{prj_top_level_tags} +\title{prj_top_level_tags} +\usage{ +prj_top_level_tags() +} +\value{ +list: List of lists. +} +\description{ +Gets top level .prj tags along with info if they are required. +} diff --git a/tests/testthat/test-generate_benchmark_script.R b/tests/testthat/test-generate_benchmark_script.R index 65f682d..359d5a7 100644 --- a/tests/testthat/test-generate_benchmark_script.R +++ b/tests/testthat/test-generate_benchmark_script.R @@ -26,7 +26,7 @@ test_that("construct_add_call works", { ogs_param_call <- construct_add_call(ogs_param) - expect_equal(ogs_param_call, paste0("ogs6_obj$add_parameter(", + expect_equal(ogs_param_call, paste0("ogs6_obj$add(", "r2ogs6_parameter(name = \"a\",\n", "type = \"t\",\n", "values = c(0, 1)))\n")) @@ -49,7 +49,7 @@ test_that("construct_add_call handles Ellipsis correctly", { ogs_param_call <- construct_add_call(ogs_parameter) expect_equal(ogs_param_call, - paste0("ogs6_obj$add_parameter(r2ogs6_parameter(name = ", + paste0("ogs6_obj$add(r2ogs6_parameter(name = ", "\"test\",\ntype = \"test\",\nindex_values = ", "list(index_values = list(index = 1,\n", "values = c(1, 2)))))\n")) diff --git a/tests/testthat/test-ogs6.R b/tests/testthat/test-ogs6.R index 8be33fe..9b1d820 100644 --- a/tests/testthat/test-ogs6.R +++ b/tests/testthat/test-ogs6.R @@ -8,7 +8,7 @@ test_that("OGS6$clear() works as expected", { sim_id = 1, sim_path = "sim_path") - ogs6_obj$add_parameter(r2ogs6_parameter( + ogs6_obj$add(r2ogs6_parameter( name = "pressure0", type = "Constant", values = 1e5 @@ -33,10 +33,8 @@ test_that("OGS6$add() works", { values = 1e5 )) - ogs6_obj$add(x = "my_script.py") - + expect_error(ogs6_obj$add("my_script.py")) expect_equal(length(ogs6_obj$parameters), 1) expect_equal(ogs6_obj$parameters[[1]]$values, 1e5) - expect_equal(ogs6_obj$python_script, "my_script.py") }) diff --git a/tests/testthat/test-ogs6_ensemble.R b/tests/testthat/test-ogs6_ensemble.R index 5616a4b..f8fc44c 100644 --- a/tests/testthat/test-ogs6_ensemble.R +++ b/tests/testthat/test-ogs6_ensemble.R @@ -8,13 +8,12 @@ test_that("OGS6_Ensemble initialization works", { sim_id = 1, sim_path = "sim_path") - ogs6_obj$add_parameter(r2ogs6_parameter( + ogs6_obj$add(r2ogs6_parameter( name = "pressure0", type = "Constant", value = 1 )) - ogs6_ens <- OGS6_Ensemble$new( ogs6_obj = ogs6_obj, parameters = list(list(ogs6_obj$parameters[[1]]$value, c(2, 3, 4))) diff --git a/tests/testthat/test-utils.R b/tests/testthat/test-utils.R index 9e50cbd..d9692b3 100644 --- a/tests/testthat/test-utils.R +++ b/tests/testthat/test-utils.R @@ -24,8 +24,8 @@ test_that("get_tag_from_xpath() works", { }) -test_that("get_prj_tag_info() works", { - expect_equal(get_prj_tag_info()[["processes"]], "r2ogs6_process") +test_that("prj_top_level_classes() works", { + expect_equal(prj_top_level_classes()[["processes"]], "r2ogs6_process") }) diff --git a/vignettes/dev_workflow_vignette.Rmd b/vignettes/dev_workflow_vignette.Rmd index 6a125a9..45c2254 100644 --- a/vignettes/dev_workflow_vignette.Rmd +++ b/vignettes/dev_workflow_vignette.Rmd @@ -138,6 +138,9 @@ xpaths_for_classes[["r2ogs6_process"]] xpaths_for_classes[["r2ogs6_convergence_criterion"]] ``` +If the class you've created is a `.prj` top level class or a child of a top level wrapper node like `processes`, add a corresponding `OGS6` private parameter and an active field. For example, the `processes` node is represented as a list, so I added the private parameter `.processes = list()` and the active field `processes`. + + A lot of things in the `r2ogs6` package work in a way that is a bit "meta". Often times, functions are called via `eval(parse(text = call_string))` where `call_string` has for example been concatenated out of info about the parameter names of a certain class. This saves a lot of code regarding import, export and script generation but requires that you've made the respective info available as shown here. So we've analysed some files, generated some code, created a new class and registered it with the package... what now? That's it actually, that's the workflow. Well, at least it's supposed to be. diff --git a/vignettes/user_workflow_vignette.Rmd b/vignettes/user_workflow_vignette.Rmd index 7322eb3..c1726db 100644 --- a/vignettes/user_workflow_vignette.Rmd +++ b/vignettes/user_workflow_vignette.Rmd @@ -99,12 +99,12 @@ As a rule of thumb, classes are named with the prefix `r2ogs6_` followed by thei Let's try adding something now. -### Adding input data via add_* +### Adding input data via OGS6$add() -To add data to our simulation object, we use one of ... . +To add data to our simulation object, we use `OGS6$add()`. ```{r} - ogs6_obj$add_parameter(r2ogs6_parameter( + ogs6_obj$add(r2ogs6_parameter( name = "pressure0", type = "Constant", value = 1 -- GitLab