Skip to content
Snippets Groups Projects
Commit f188c39e authored by Ruben Heinrich's avatar Ruben Heinrich
Browse files

[base] moved function xpath_for_classes out of R folder

parent f224dfbb
No related branches found
No related tags found
1 merge request!7Merge 7 fixed functionality into master
......@@ -357,12 +357,6 @@ construct_add_call <- function(object, nested_call = FALSE) {
#If call isn't nested, it has a OGS6$add_* function
if(!nested_call){
# if(tag_name == "vtu"){
# filename_str <- paste0(",\npaste0(ogs6_obj$sim_path,\n",
# "basename(ogs6_obj$geometry))")
# }
ret_str <- paste0("ogs6_obj$add_", tag_name,
"(", ret_str, ")\n")
}
......@@ -442,7 +436,7 @@ delete_empty_from_str <- function(string){
#'delete_keywords_from_str
#'@description Utility function to delete keywords from a string,
#' this important because there is a <repeat> tag in <time_loop> and
#' this is important because there is a <repeat> tag in <time_loop> and
#' "repeat" is a reserved word in R (extend this function if you find more
#' reserved words)
#'@param string string
......
......@@ -21,7 +21,7 @@ generate_constructor <- function(params,
assertthat::assert_that(length(params) == 4)
assertthat::assert_that(assertthat::is.string(prefix))
xpath <- params[[1]]
xpath <- stringr::str_remove(params[[1]], "\\/[A-Za-z_]*\\/")
tag_name <- get_tag_from_xpath(xpath)
attr_flags <- params[[3]]
......@@ -82,7 +82,7 @@ generate_helper <- function(params,
assertthat::assert_that(length(params) == 4)
assertthat::assert_that(assertthat::is.string(prefix))
xpath <- params[[1]]
xpath <- stringr::str_remove(params[[1]], "\\/[A-Za-z_]*\\/")
tag_name <- get_tag_from_xpath(xpath)
param_flags <- params[[4]]
......@@ -256,7 +256,7 @@ generate_R6 <- function(params,
assertthat::assert_that(is.list(params))
assertthat::assert_that(length(params) == 4)
xpath <- params[[1]]
xpath <- stringr::str_remove(params[[1]], "\\/[A-Za-z_]*\\/")
tag_name <- get_tag_from_xpath(xpath)
attr_flags <- params[[3]]
......
......@@ -51,7 +51,8 @@ read_in <- function(ogs6_obj,
return(invisible(NULL))
}
xpath <- stringr::str_remove(xpath, "\\/OpenGeoSysProject\\/")
# Remove root expression for better readability
xpath <- stringr::str_remove(xpath, "\\/[A-Za-z_]*\\/")
r2ogs6_obj <- NULL
......
File deleted
......@@ -2,58 +2,6 @@
#===== Implementation utility =====
#'get_xpaths_for_classes
#'@description Creates a list of all `xpath` arguments of `r2ogs6` classes.
#' This is for efficiency as getting arguments from non-instantiated S3 classes
#' requires string parsing.
get_xpaths_for_classes <- function(){
exports <- r2ogs6_ns_exports
r2ogs6_class_constructor_names <-
sort(exports[grepl("new_r2ogs6", exports)])
r2ogs6_class_helper_names <-
sort(exports[grepl("^r2ogs6", exports)])
xfc_list <- list()
for(i in seq_len(length(r2ogs6_class_constructor_names))){
cc <- r2ogs6_class_constructor_names[[i]]
cc_str <-
paste(utils::capture.output(dput(eval(parse(text = cc)))),
collapse="\n")
if(grepl("xpath[ ]*=[ \r\n]*\"[A-Za-z\\_\\/]*\"", cc_str)){
xpath <-
stringr::str_extract(cc_str,
"xpath[ ]*=[ \r\n]*\"[A-Za-z\\_\\/]*\"")
xpath <- unlist(strsplit(xpath, "[ ]*=[ \r\n]*"))[[2]]
xpath <- stringr::str_remove_all(xpath, "\"")
}else{
# If xpath was concatenated, parse
regexp <- paste0("xpath[:space:]*=[^=]*")
xpath_call <- stringr::str_extract(cc_str, regexp)
xpath_call <- stringr::str_remove(xpath_call,
",[:space:]*attr_name.*")
xpath_call <- unlist(strsplit(xpath_call, "[ ]*=[ \r\n]*"))[[2]]
xpath <- eval(parse(text = xpath_call))
}
xfc_list <- c(xfc_list,
list(xpath))
names(xfc_list)[[length(xfc_list)]] <-
r2ogs6_class_helper_names[[i]]
}
return(invisible(xfc_list))
}
#'get_class_from_xpath
#'@description Gets r2ogs6 class name from an xpath-like expression
#'@param xpath string: An xpath expression. Works for path-like xpaths only
......
# global Python references (will be initialized in .onLoad)
# Set global variables
# Python vtk library reference
vtk <- NULL
.onLoad <- function(libname, pkgname){
......@@ -51,6 +53,7 @@ vtk <- NULL
.onAttach <- function(libname, pkgname){
packageStartupMessage(
paste("r2ogs6 works best with its options set :)\nFor",
"an overview, use the command",
......
# While having r2ogs6 loaded:
r2ogs6_ns_exports <- getNamespaceExports("r2ogs6")
usethis::use_data(r2ogs6_ns_exports,
internal = TRUE,
overwrite = TRUE)
# While having r2ogs6 loaded:
#'get_xpaths_for_classes
#'@description Creates a list of all `xpath` arguments of `r2ogs6` classes.
#' This is for efficiency as getting arguments from non-instantiated S3 classes
#' requires string parsing.
get_xpaths_for_classes <- function(){
ns_exports <- getNamespaceExports("r2ogs6")
r2ogs6_class_constructor_names <-
sort(ns_exports[grepl("^new_r2ogs6", ns_exports)])
r2ogs6_class_helper_names <-
sort(ns_exports[grepl("^r2ogs6", ns_exports)])
xfc_list <- list()
for(i in seq_len(length(r2ogs6_class_constructor_names))){
cc <- r2ogs6_class_constructor_names[[i]]
cc_str <-
paste(utils::capture.output(dput(eval(parse(text = cc)))),
collapse="\n")
if(grepl("xpath[ ]*=[ \r\n]*\"[A-Za-z\\_\\/]*\"", cc_str)){
xpath <-
stringr::str_extract(cc_str,
"xpath[ ]*=[ \r\n]*\"[A-Za-z\\_\\/]*\"")
xpath <- unlist(strsplit(xpath, "[ ]*=[ \r\n]*"))[[2]]
xpath <- stringr::str_remove_all(xpath, "\"")
}else{
# If xpath was concatenated, parse
regexp <- paste0("xpath[:space:]*=[^=]*")
xpath_call <- stringr::str_extract(cc_str, regexp)
xpath_call <- stringr::str_remove(xpath_call,
",[:space:]*attr_name.*")
xpath_call <- unlist(strsplit(xpath_call, "[ ]*=[ \r\n]*"))[[2]]
xpath <- eval(parse(text = xpath_call))
}
xfc_list <- c(xfc_list,
list(xpath))
names(xfc_list)[[length(xfc_list)]] <-
r2ogs6_class_helper_names[[i]]
}
return(invisible(xfc_list))
}
xpaths_for_classes <- get_xpaths_for_classes()
usethis::use_data(xpaths_for_classes,
......
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/utils.R
\name{get_xpaths_for_classes}
\alias{get_xpaths_for_classes}
\title{get_xpaths_for_classes}
\usage{
get_xpaths_for_classes()
}
\description{
Creates a list of all `xpath` arguments of `r2ogs6` classes.
This is for efficiency as getting arguments from non-instantiated S3 classes
requires string parsing.
}
......@@ -2,12 +2,6 @@
#===== Implementation utility =====
test_that("get_xpaths_for_classes() works", {
expect_equal(get_xpaths_for_classes()[["r2ogs6_process"]],
"processes/process")
})
test_that("get_class_from_xpath() works", {
expect_equal(get_class_from_xpath("processes/process"),
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment