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

[bugfix] Fixed mesh read in error

parent 4a4b37fe
No related branches found
No related tags found
1 merge request!20Resolve "Prepare package for installation"
...@@ -20,17 +20,16 @@ export_prj <- function(ogs6_obj) { ...@@ -20,17 +20,16 @@ export_prj <- function(ogs6_obj) {
#If there is a .gml defined, add "mesh" node, else add "meshes" node #If there is a .gml defined, add "mesh" node, else add "meshes" node
if(is.null(ogs6_obj$geometry)) { if(is.null(ogs6_obj$geometry)) {
basenames <- lapply(ogs6_obj$meshes, function(x){basename(x)}) meshes_node <- meshes_to_xml(ogs6_obj$meshes)
meshes_node <- to_node(basenames, "meshes")
}else{ }else{
xml2::xml_add_child( xml2::xml_add_child(
prj_xml, prj_xml,
xml2::as_xml_document(to_node(ogs6_obj$geometry))) xml2::as_xml_document(to_node(ogs6_obj$geometry)))
meshes_node <- to_node(basename(ogs6_obj$meshes[[1]]), "mesh") meshes_node <- meshes_to_xml(ogs6_obj$meshes)
} }
xml2::xml_add_child(prj_xml, xml2::xml_add_child(prj_xml,
xml2::as_xml_document(meshes_node)) meshes_node)
#Get implemented classes #Get implemented classes
prj_components <- ogs6_prj_top_level_classes() prj_components <- ogs6_prj_top_level_classes()
......
...@@ -98,6 +98,7 @@ OGS6 <- R6::R6Class("OGS6", ...@@ -98,6 +98,7 @@ OGS6 <- R6::R6Class("OGS6",
#' Adds a reference to a \code{.vtu} file and optionally, a \code{OGS6_vtu} #' Adds a reference to a \code{.vtu} file and optionally, a \code{OGS6_vtu}
#' object #' object
#' @param path string: A path #' @param path string: A path
#' @param axisym flag: Is the mesh axially symmetrical?
#' @param read_in_vtu flag: Optional: Should \code{.vtu} file just be #' @param read_in_vtu flag: Optional: Should \code{.vtu} file just be
#' copied or read in too? #' copied or read in too?
#' @examples #' @examples
...@@ -105,12 +106,16 @@ OGS6 <- R6::R6Class("OGS6", ...@@ -105,12 +106,16 @@ OGS6 <- R6::R6Class("OGS6",
#' ogs6_obj$add_vtu("this_works.vtu") #' ogs6_obj$add_vtu("this_works.vtu")
#' \dontrun{ogs6_obj$add_vtu("this_doesnt.oops")} #' \dontrun{ogs6_obj$add_vtu("this_doesnt.oops")}
add_vtu = function(path, add_vtu = function(path,
axisym = FALSE,
read_in_vtu = FALSE){ read_in_vtu = FALSE){
assertthat::assert_that(assertthat::is.string(path)) assertthat::assert_that(assertthat::is.string(path))
assertthat::assert_that(grepl("\\.vtu$", path)) assertthat::assert_that(grepl("\\.vtu$", path))
assertthat::assert_that(assertthat::is.flag(axisym))
assertthat::assert_that(assertthat::is.flag(read_in_vtu)) assertthat::assert_that(assertthat::is.flag(read_in_vtu))
self$meshes <- c(self$meshes, mesh = path) self$meshes <- c(self$meshes,
list(mesh = list(path = path,
axially_symmetric = axisym)))
if(read_in_vtu){ if(read_in_vtu){
private$.vtus <- c(private$.vtus, list(OGS6_vtu$new(path))) private$.vtus <- c(private$.vtus, list(OGS6_vtu$new(path)))
...@@ -328,12 +333,15 @@ OGS6 <- R6::R6Class("OGS6", ...@@ -328,12 +333,15 @@ OGS6 <- R6::R6Class("OGS6",
}else{ }else{
assertthat::assert_that(is.list(value)) assertthat::assert_that(is.list(value))
lapply(value, function(x){ lapply(value, function(x){
assertthat::assert_that(assertthat::is.string(x)) assertthat::assert_that(is.list(x), length(x) == 2)
assertthat::assert_that(assertthat::is.string(x[[1]]))
assertthat::assert_that(assertthat::is.flag(x[[2]]))
}) })
private$.meshes <- value private$.meshes <- value
} }
}, },
#' @field vtus #' @field vtus
#' \code{.vtu}s. \code{value} must be list of \code{OGS6_vtu} objects #' \code{.vtu}s. \code{value} must be list of \code{OGS6_vtu} objects
vtus = function(value) { vtus = function(value) {
......
...@@ -146,12 +146,6 @@ OGS6_gml <- R6::R6Class( ...@@ -146,12 +146,6 @@ OGS6_gml <- R6::R6Class(
} }
}, },
#'@field is_subclass
#'Getter for private parameter '.is_subclass'
is_subclass = function(value) {
private$.is_subclass
},
#'@field attr_names #'@field attr_names
#'Getter for private parameter '.attr_names' #'Getter for private parameter '.attr_names'
attr_names = function(value) { attr_names = function(value) {
...@@ -197,7 +191,6 @@ OGS6_gml <- R6::R6Class( ...@@ -197,7 +191,6 @@ OGS6_gml <- R6::R6Class(
.points = NULL, .points = NULL,
.polylines = NULL, .polylines = NULL,
.surfaces = NULL, .surfaces = NULL,
.is_subclass = TRUE,
.attr_names = c("point", "name", "id", "element"), .attr_names = c("point", "name", "id", "element"),
.flatten_on_exp = character() .flatten_on_exp = character()
) )
......
...@@ -58,8 +58,17 @@ read_in_prj <- function(ogs6_obj, ...@@ -58,8 +58,17 @@ read_in_prj <- function(ogs6_obj,
vtu_ref <- xml2::xml_text(vtu_ref_nodes[[i]]) vtu_ref <- xml2::xml_text(vtu_ref_nodes[[i]])
vtu_path <- paste0(dirname(prj_path), "/", vtu_ref) vtu_path <- paste0(dirname(prj_path), "/", vtu_ref)
axisym_val <- xml2::xml_attr(vtu_ref_nodes[[i]], "axially_symmetric")
if(!is.na(axisym_val) && axisym_val == "true"){
axisym_val <- TRUE
}else{
axisym_val <- FALSE
}
# Read in .vtu file(s) or just save their path # Read in .vtu file(s) or just save their path
ogs6_obj$add_vtu(path = vtu_path, ogs6_obj$add_vtu(path = vtu_path,
axisym = axisym_val,
read_in_vtu = read_in_vtu) read_in_vtu = read_in_vtu)
} }
......
...@@ -96,7 +96,7 @@ ogs6_export_sim_files <- function(ogs6_obj, ...@@ -96,7 +96,7 @@ ogs6_export_sim_files <- function(ogs6_obj,
# Copy all referenced .vtu files to ogs6_obj$sim_path # Copy all referenced .vtu files to ogs6_obj$sim_path
lapply(ogs6_obj$meshes, function(x){ lapply(ogs6_obj$meshes, function(x){
file.copy(x, ogs6_obj$sim_path) file.copy(x[["path"]], ogs6_obj$sim_path)
}) })
if(!is.null(ogs6_obj$python_script)){ if(!is.null(ogs6_obj$python_script)){
......
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