Skip to content
Snippets Groups Projects
Commit e0e9d6e6 authored by Johannes Boog's avatar Johannes Boog
Browse files

Merge branch '46-bugfix_set_read_in_gml_flag' into 'master'

[docs] examples polished

Closes #46, #49, #48, and #50

See merge request !31
parents ccf5e97e 0e5c68f7
No related branches found
No related tags found
1 merge request!31[docs] examples polished
Showing with 1617 additions and 173 deletions
......@@ -36,6 +36,11 @@ export_prj <- function(ogs6_obj) {
# Include file reference
if(names(ogs6_obj$processes)[[1]] == "include"){
# update path to referenced file as reference has to be relative to
# the *.prj file location, just remove sim_path
new_ref_path <- gsub(ogs6_obj$sim_path, "",
ogs6_obj$processes[[1]][["file"]])
ogs6_obj$processes <- new_ref_path
processes_node <- to_node(ogs6_obj$processes,
attribute_names = "include")
......
......@@ -10,6 +10,7 @@
#' @inheritParams ogs6_generate_benchmark_script
#' @param starting_from_prj_path string: Optional: `.prj` path to start from
#' @param skip_prj_paths character: Optional: `.prj` paths to skip
#' @param only_prj_files character: Optional: `.prj` files to limit to.
#' @export
ogs6_generate_benchmark_scripts <-
function(path,
......@@ -18,7 +19,8 @@ ogs6_generate_benchmark_scripts <-
read_in_gml,
read_in_vtu = FALSE,
starting_from_prj_path = "",
skip_prj_paths = character()){
skip_prj_paths = character(),
only_prj_files = character()){
if(missing(path)){
path <- unlist(options("r2ogs6.default_benchmark_path"))
......@@ -40,6 +42,7 @@ ogs6_generate_benchmark_scripts <-
script_path <- as_dir_path(script_path)
assertthat::assert_that(assertthat::is.string(starting_from_prj_path))
assertthat::assert_that(is.character(skip_prj_paths))
assertthat::assert_that(is.character(only_prj_files))
prj_paths <- list.files(path = path,
pattern = "\\.prj$",
......@@ -78,6 +81,12 @@ ogs6_generate_benchmark_scripts <-
next
}
if(!(missing(only_prj_files))){
if(!(basename(prj_paths[[i]]) %in% only_prj_files)){
next
}
}
# cat("\nGenerating script from path", prj_paths[[i]])
# Put simulations in their own subfolders under sim_path
......@@ -139,7 +148,7 @@ ogs6_generate_benchmark_script <- function(prj_path,
sim_path,
ogs6_bin_path,
script_path,
read_in_gml,
read_in_gml = FALSE,
read_in_vtu = FALSE) {
if(missing(sim_path)){
......@@ -166,8 +175,8 @@ ogs6_generate_benchmark_script <- function(prj_path,
read_in_prj(ogs6_obj,
prj_path,
read_in_vtu,
read_in_gml = FALSE)
read_in_gml = FALSE,
read_in_vtu)
prj_components = ogs6_prj_top_level_classes()
......@@ -208,11 +217,12 @@ ogs6_generate_benchmark_script <- function(prj_path,
# Add .vtu references and optionally, OGS6_vtu objects
for(i in seq_len(length(ogs6_obj$meshes))){
script_str <- paste0(script_str,
"ogs6_obj$add_vtu(",
construct_add_call(ogs6_obj$meshes[[i]]), ",\n",
read_in_vtu,
")\n\n")
script_str <-
paste0(script_str,
"ogs6_obj$add_vtu(path = \"",
ogs6_obj$meshes[[i]]$path, "\",\n",
"axisym = ", ogs6_obj$meshes[[i]]$axially_symmetric, ",\n",
"read_in_vtu = ", read_in_vtu, ")\n\n")
}
# Add class objects (and such in wrapper lists)
......@@ -233,10 +243,20 @@ ogs6_generate_benchmark_script <- function(prj_path,
}
for(j in seq_along(ogs6_component)){
script_str <-
paste0(script_str,
paste0(construct_add_call(ogs6_component[[j]]),
"\n\n"))
# TODO(boog): this is just an quick and dirty solution for the
# include tag for now
if(!is.null(names(ogs6_component[j])) &
all(names(ogs6_component[j])=="include")){
script_str <-
paste0(script_str,
get_component_call, " <- \"", ogs6_component[[j]],
"\"\n\n")
}else{
script_str <-
paste0(script_str,
paste0(construct_add_call(ogs6_component[[j]]),
"\n\n"))
}
}
}
......
......@@ -24,8 +24,10 @@ dsa <- NULL
if(file.exists("config.yml")){
cfg <- config::get()
for(i in names(op.r2ogs6)){
eval(parse(text = paste0("options(", i, " = cfg$", i, ")")))
for(i in names(cfg)){
if(i %in% names(op.r2ogs6)) {
eval(parse(text = paste0("options(", i, " = cfg$", i, ")")))
}
}
}
......
library(r2ogs6)
#===== Set up simulation object =====
# First make sure you're ready to go by setting r2ogs6.default_ogs_bin_path.
# You can do this by commenting out the line below and modifying the path to
# fit your system.
# options("r2ogs6.default_ogs_bin_path" = "your_path_here")
# Then we can create a simulation object.
ogs6_obj <- OGS6$new(sim_name = "axisym_theis",
sim_path = "D:/OGS_Sim/")
#===== Read in benchmark file =====
# Modify the prj_path depending on where you saved the benchmark file.
prj_path <- "inst/extdata/benchmarks/AxiSymTheis/axisym_theis.prj"
# Read in the benchmark into our simulation object
read_in_prj(ogs6_obj, prj_path, T)
#===== Run simulation =====
e <- run_simulation(ogs6_obj)
library(r2ogs6)
#===== Set up simulation object =====
# First make sure you're ready to go by setting r2ogs6.default_ogs_bin_path.
# You can do this by commenting out the line below and modifying the path to
# fit your system.
# options("r2ogs6.default_ogs_bin_path" = "your_path_here")
# Then we can create a simulation object.
ogs6_obj <- OGS6$new(sim_name = "theis",
sim_id = 1,
sim_path = "D:/OGS_Sim/")
#===== Read in benchmark file =====
# Modify the prj_path depending on where you saved the benchmark file.
prj_path <- "inst/extdata/benchmarks/theis_well_pumping/theis.prj"
# Read in the benchmark into our simulation object
read_in_prj(ogs6_obj, prj_path)
#===== Run simulation =====
e <- run_simulation(ogs6_obj)
library(r2ogs6)
#===== Set up simulation object =====
# First make sure you're ready to go by setting r2ogs6.default_ogs_bin_path.
# You can do this by commenting out the line below and modifying the path to
# fit your system.
# options("r2ogs6.default_ogs_bin_path" = "your_path_here")
# Then we can create a simulation object.
ogs6_obj <- OGS6$new(sim_name = "my_sim",
sim_id = 1,
sim_path = "D:/OGS_Sim/")
#===== Read in benchmark file =====
# Modify the prj_path depending on where you saved the benchmark file.
prj_path <- "inst/extdata/flow_free_expansion/flow_free_expansion.prj"
# Read in the benchmark into our simulation object
read_in_prj(ogs6_obj, prj_path)
#===== Create ensemble from simulation object =====
ogs6_ens <- OGS6_Ensemble$new(
ogs6_obj = ogs6_obj,
parameters = list(list(ogs6_obj$parameters[[2]]$value, c(0.2, 0.3, 0.4)))
)
#===== Run simulation =====
# Should work on machines with more RAM
ogs6_ens$run_simulation(parallel = TRUE)
......@@ -9,13 +9,13 @@ library(r2ogs6)
# You can do this by commenting out the line below and modifying the path to
# fit your system.
# options("r2ogs6.default_ogs_bin_path" = "your_path_here")
# options("r2ogs6.default_ogs6_bin_path" = "your_path_here")
# Then we can create a simulation object.
tmpdir <- tempdir()
ogs6_obj <- OGS6$new(sim_name = "flow_free_expansion",
sim_path = "D:/OGS_Sim/")
sim_path = tmpdir)
#===== Read in benchmark file =====
......@@ -24,10 +24,8 @@ ogs6_obj <- OGS6$new(sim_name = "flow_free_expansion",
prj_path <- "inst/extdata/benchmarks/flow_free_expansion/flow_free_expansion.prj"
# Read in the benchmark into our simulation object
read_in_prj(ogs6_obj, prj_path)
read_in_prj(ogs6_obj, prj_path, read_in_gml = T)
#===== Run simulation =====
e <- ogs6_run_simulation(ogs6_obj, write_logfile = FALSE)
......@@ -34,7 +34,7 @@
<name>concentration</name>
<properties>
<property>
<name>molecular_diffusion</name>
<name>pore_diffusion</name>
<type>Constant</type>
<value>2e-9</value>
</property>
......
<!DOCTYPE html>
<html>
<head>
<meta charset="utf-8" />
<meta name="generator" content="pandoc" />
<meta http-equiv="X-UA-Compatible" content="IE=EDGE" />
<meta name="viewport" content="width=device-width, initial-scale=1" />
<meta name="author" content="Ruben Heinrich" />
<title>r2ogs6 Developer Guide</title>
<script src="data:application/javascript;base64,Ly8gUGFuZG9jIDIuOSBhZGRzIGF0dHJpYnV0ZXMgb24gYm90aCBoZWFkZXIgYW5kIGRpdi4gV2UgcmVtb3ZlIHRoZSBmb3JtZXIgKHRvCi8vIGJlIGNvbXBhdGlibGUgd2l0aCB0aGUgYmVoYXZpb3Igb2YgUGFuZG9jIDwgMi44KS4KZG9jdW1lbnQuYWRkRXZlbnRMaXN0ZW5lcignRE9NQ29udGVudExvYWRlZCcsIGZ1bmN0aW9uKGUpIHsKICB2YXIgaHMgPSBkb2N1bWVudC5xdWVyeVNlbGVjdG9yQWxsKCJkaXYuc2VjdGlvbltjbGFzcyo9J2xldmVsJ10gPiA6Zmlyc3QtY2hpbGQiKTsKICB2YXIgaSwgaCwgYTsKICBmb3IgKGkgPSAwOyBpIDwgaHMubGVuZ3RoOyBpKyspIHsKICAgIGggPSBoc1tpXTsKICAgIGlmICghL15oWzEtNl0kL2kudGVzdChoLnRhZ05hbWUpKSBjb250aW51ZTsgIC8vIGl0IHNob3VsZCBiZSBhIGhlYWRlciBoMS1oNgogICAgYSA9IGguYXR0cmlidXRlczsKICAgIHdoaWxlIChhLmxlbmd0aCA+IDApIGgucmVtb3ZlQXR0cmlidXRlKGFbMF0ubmFtZSk7CiAgfQp9KTsK"></script>
<link href="data:text/css,%0Aa%2Eanchor%2Dsection%20%7Bmargin%2Dleft%3A%2010px%3B%20visibility%3A%20hidden%3B%20color%3A%20inherit%3B%7D%0Aa%2Eanchor%2Dsection%3A%3Abefore%20%7Bcontent%3A%20%27%23%27%3B%7D%0A%2EhasAnchor%3Ahover%20a%2Eanchor%2Dsection%20%7Bvisibility%3A%20visible%3B%7D%0A" rel="stylesheet" />
<script src="data:application/javascript;base64,Ly8gQW5jaG9yIHNlY3Rpb25zIHYxLjAgd3JpdHRlbiBieSBBdHN1c2hpIFlhc3Vtb3RvIG9uIE9jdCAzcmQsIDIwMjAuCmRvY3VtZW50LmFkZEV2ZW50TGlzdGVuZXIoJ0RPTUNvbnRlbnRMb2FkZWQnLCBmdW5jdGlvbigpIHsKICAvLyBEbyBub3RoaW5nIGlmIEFuY2hvckpTIGlzIHVzZWQKICBpZiAodHlwZW9mIHdpbmRvdy5hbmNob3JzID09PSAnb2JqZWN0JyAmJiBhbmNob3JzLmhhc093blByb3BlcnR5KCdoYXNBbmNob3JKU0xpbmsnKSkgewogICAgcmV0dXJuOwogIH0KCiAgY29uc3QgaCA9IGRvY3VtZW50LnF1ZXJ5U2VsZWN0b3JBbGwoJ2gxLCBoMiwgaDMsIGg0LCBoNSwgaDYnKTsKCiAgLy8gRG8gbm90aGluZyBpZiBzZWN0aW9ucyBhcmUgYWxyZWFkeSBhbmNob3JlZAogIGlmIChBcnJheS5mcm9tKGgpLnNvbWUoeCA9PiB4LmNsYXNzTGlzdC5jb250YWlucygnaGFzQW5jaG9yJykpKSB7CiAgICByZXR1cm4gbnVsbDsKICB9CgogIC8vIFVzZSBzZWN0aW9uIGlkIHdoZW4gcGFuZG9jIHJ1bnMgd2l0aCAtLXNlY3Rpb24tZGl2cwogIGNvbnN0IHNlY3Rpb25faWQgPSBmdW5jdGlvbih4KSB7CiAgICByZXR1cm4gKCh4LmNsYXNzTGlzdC5jb250YWlucygnc2VjdGlvbicpIHx8ICh4LnRhZ05hbWUgPT09ICdTRUNUSU9OJykpCiAgICAgICAgICAgID8geC5pZCA6ICcnKTsKICB9OwoKICAvLyBBZGQgYW5jaG9ycwogIGguZm9yRWFjaChmdW5jdGlvbih4KSB7CiAgICBjb25zdCBpZCA9IHguaWQgfHwgc2VjdGlvbl9pZCh4LnBhcmVudEVsZW1lbnQpOwogICAgaWYgKGlkID09PSAnJykgewogICAgICByZXR1cm4gbnVsbDsKICAgIH0KICAgIGxldCBhbmNob3IgPSBkb2N1bWVudC5jcmVhdGVFbGVtZW50KCdhJyk7CiAgICBhbmNob3IuaHJlZiA9ICcjJyArIGlkOwogICAgYW5jaG9yLmNsYXNzTGlzdCA9IFsnYW5jaG9yLXNlY3Rpb24nXTsKICAgIHguY2xhc3NMaXN0LmFkZCgnaGFzQW5jaG9yJyk7CiAgICB4LmFwcGVuZENoaWxkKGFuY2hvcik7CiAgfSk7Cn0pOwo="></script>
<style type="text/css">
code{white-space: pre-wrap;}
span.smallcaps{font-variant: small-caps;}
span.underline{text-decoration: underline;}
div.column{display: inline-block; vertical-align: top; width: 50%;}
div.hanging-indent{margin-left: 1.5em; text-indent: -1.5em;}
ul.task-list{list-style: none;}
</style>
<style type="text/css">code{white-space: pre;}</style>
<style type="text/css" data-origin="pandoc">
pre > code.sourceCode { white-space: pre; position: relative; }
pre > code.sourceCode > span { display: inline-block; line-height: 1.25; }
pre > code.sourceCode > span:empty { height: 1.2em; }
.sourceCode { overflow: visible; }
code.sourceCode > span { color: inherit; text-decoration: inherit; }
div.sourceCode { margin: 1em 0; }
pre.sourceCode { margin: 0; }
@media screen {
div.sourceCode { overflow: auto; }
}
@media print {
pre > code.sourceCode { white-space: pre-wrap; }
pre > code.sourceCode > span { text-indent: -5em; padding-left: 5em; }
}
pre.numberSource code
{ counter-reset: source-line 0; }
pre.numberSource code > span
{ position: relative; left: -4em; counter-increment: source-line; }
pre.numberSource code > span > a:first-child::before
{ content: counter(source-line);
position: relative; left: -1em; text-align: right; vertical-align: baseline;
border: none; display: inline-block;
-webkit-touch-callout: none; -webkit-user-select: none;
-khtml-user-select: none; -moz-user-select: none;
-ms-user-select: none; user-select: none;
padding: 0 4px; width: 4em;
color: #aaaaaa;
}
pre.numberSource { margin-left: 3em; border-left: 1px solid #aaaaaa; padding-left: 4px; }
div.sourceCode
{ }
@media screen {
pre > code.sourceCode > span > a:first-child::before { text-decoration: underline; }
}
code span.al { color: #ff0000; font-weight: bold; } /* Alert */
code span.an { color: #60a0b0; font-weight: bold; font-style: italic; } /* Annotation */
code span.at { color: #7d9029; } /* Attribute */
code span.bn { color: #40a070; } /* BaseN */
code span.bu { } /* BuiltIn */
code span.cf { color: #007020; font-weight: bold; } /* ControlFlow */
code span.ch { color: #4070a0; } /* Char */
code span.cn { color: #880000; } /* Constant */
code span.co { color: #60a0b0; font-style: italic; } /* Comment */
code span.cv { color: #60a0b0; font-weight: bold; font-style: italic; } /* CommentVar */
code span.do { color: #ba2121; font-style: italic; } /* Documentation */
code span.dt { color: #902000; } /* DataType */
code span.dv { color: #40a070; } /* DecVal */
code span.er { color: #ff0000; font-weight: bold; } /* Error */
code span.ex { } /* Extension */
code span.fl { color: #40a070; } /* Float */
code span.fu { color: #06287e; } /* Function */
code span.im { } /* Import */
code span.in { color: #60a0b0; font-weight: bold; font-style: italic; } /* Information */
code span.kw { color: #007020; font-weight: bold; } /* Keyword */
code span.op { color: #666666; } /* Operator */
code span.ot { color: #007020; } /* Other */
code span.pp { color: #bc7a00; } /* Preprocessor */
code span.sc { color: #4070a0; } /* SpecialChar */
code span.ss { color: #bb6688; } /* SpecialString */
code span.st { color: #4070a0; } /* String */
code span.va { color: #19177c; } /* Variable */
code span.vs { color: #4070a0; } /* VerbatimString */
code span.wa { color: #60a0b0; font-weight: bold; font-style: italic; } /* Warning */
</style>
<script>
// apply pandoc div.sourceCode style to pre.sourceCode instead
(function() {
var sheets = document.styleSheets;
for (var i = 0; i < sheets.length; i++) {
if (sheets[i].ownerNode.dataset["origin"] !== "pandoc") continue;
try { var rules = sheets[i].cssRules; } catch (e) { continue; }
for (var j = 0; j < rules.length; j++) {
var rule = rules[j];
// check if there is a div.sourceCode rule
if (rule.type !== rule.STYLE_RULE || rule.selectorText !== "div.sourceCode") continue;
var style = rule.style.cssText;
// check if color or background-color is set
if (rule.style.color === '' && rule.style.backgroundColor === '') continue;
// replace div.sourceCode by a pre.sourceCode rule
sheets[i].deleteRule(j);
sheets[i].insertRule('pre.sourceCode{' + style + '}', j);
}
}
})();
</script>
<link rel="stylesheet" href="data:text/css,body%20%7B%0Abackground%2Dcolor%3A%20%23fff%3B%0Amargin%3A%201em%20auto%3B%0Amax%2Dwidth%3A%20700px%3B%0Aoverflow%3A%20visible%3B%0Apadding%2Dleft%3A%202em%3B%0Apadding%2Dright%3A%202em%3B%0Afont%2Dfamily%3A%20%22Open%20Sans%22%2C%20%22Helvetica%20Neue%22%2C%20Helvetica%2C%20Arial%2C%20sans%2Dserif%3B%0Afont%2Dsize%3A%2014px%3B%0Aline%2Dheight%3A%201%2E35%3B%0A%7D%0A%23TOC%20%7B%0Aclear%3A%20both%3B%0Amargin%3A%200%200%2010px%2010px%3B%0Apadding%3A%204px%3B%0Awidth%3A%20400px%3B%0Aborder%3A%201px%20solid%20%23CCCCCC%3B%0Aborder%2Dradius%3A%205px%3B%0Abackground%2Dcolor%3A%20%23f6f6f6%3B%0Afont%2Dsize%3A%2013px%3B%0Aline%2Dheight%3A%201%2E3%3B%0A%7D%0A%23TOC%20%2Etoctitle%20%7B%0Afont%2Dweight%3A%20bold%3B%0Afont%2Dsize%3A%2015px%3B%0Amargin%2Dleft%3A%205px%3B%0A%7D%0A%23TOC%20ul%20%7B%0Apadding%2Dleft%3A%2040px%3B%0Amargin%2Dleft%3A%20%2D1%2E5em%3B%0Amargin%2Dtop%3A%205px%3B%0Amargin%2Dbottom%3A%205px%3B%0A%7D%0A%23TOC%20ul%20ul%20%7B%0Amargin%2Dleft%3A%20%2D2em%3B%0A%7D%0A%23TOC%20li%20%7B%0Aline%2Dheight%3A%2016px%3B%0A%7D%0Atable%20%7B%0Amargin%3A%201em%20auto%3B%0Aborder%2Dwidth%3A%201px%3B%0Aborder%2Dcolor%3A%20%23DDDDDD%3B%0Aborder%2Dstyle%3A%20outset%3B%0Aborder%2Dcollapse%3A%20collapse%3B%0A%7D%0Atable%20th%20%7B%0Aborder%2Dwidth%3A%202px%3B%0Apadding%3A%205px%3B%0Aborder%2Dstyle%3A%20inset%3B%0A%7D%0Atable%20td%20%7B%0Aborder%2Dwidth%3A%201px%3B%0Aborder%2Dstyle%3A%20inset%3B%0Aline%2Dheight%3A%2018px%3B%0Apadding%3A%205px%205px%3B%0A%7D%0Atable%2C%20table%20th%2C%20table%20td%20%7B%0Aborder%2Dleft%2Dstyle%3A%20none%3B%0Aborder%2Dright%2Dstyle%3A%20none%3B%0A%7D%0Atable%20thead%2C%20table%20tr%2Eeven%20%7B%0Abackground%2Dcolor%3A%20%23f7f7f7%3B%0A%7D%0Ap%20%7B%0Amargin%3A%200%2E5em%200%3B%0A%7D%0Ablockquote%20%7B%0Abackground%2Dcolor%3A%20%23f6f6f6%3B%0Apadding%3A%200%2E25em%200%2E75em%3B%0A%7D%0Ahr%20%7B%0Aborder%2Dstyle%3A%20solid%3B%0Aborder%3A%20none%3B%0Aborder%2Dtop%3A%201px%20solid%20%23777%3B%0Amargin%3A%2028px%200%3B%0A%7D%0Adl%20%7B%0Amargin%2Dleft%3A%200%3B%0A%7D%0Adl%20dd%20%7B%0Amargin%2Dbottom%3A%2013px%3B%0Amargin%2Dleft%3A%2013px%3B%0A%7D%0Adl%20dt%20%7B%0Afont%2Dweight%3A%20bold%3B%0A%7D%0Aul%20%7B%0Amargin%2Dtop%3A%200%3B%0A%7D%0Aul%20li%20%7B%0Alist%2Dstyle%3A%20circle%20outside%3B%0A%7D%0Aul%20ul%20%7B%0Amargin%2Dbottom%3A%200%3B%0A%7D%0Apre%2C%20code%20%7B%0Abackground%2Dcolor%3A%20%23f7f7f7%3B%0Aborder%2Dradius%3A%203px%3B%0Acolor%3A%20%23333%3B%0Awhite%2Dspace%3A%20pre%2Dwrap%3B%20%0A%7D%0Apre%20%7B%0Aborder%2Dradius%3A%203px%3B%0Amargin%3A%205px%200px%2010px%200px%3B%0Apadding%3A%2010px%3B%0A%7D%0Apre%3Anot%28%5Bclass%5D%29%20%7B%0Abackground%2Dcolor%3A%20%23f7f7f7%3B%0A%7D%0Acode%20%7B%0Afont%2Dfamily%3A%20Consolas%2C%20Monaco%2C%20%27Courier%20New%27%2C%20monospace%3B%0Afont%2Dsize%3A%2085%25%3B%0A%7D%0Ap%20%3E%20code%2C%20li%20%3E%20code%20%7B%0Apadding%3A%202px%200px%3B%0A%7D%0Adiv%2Efigure%20%7B%0Atext%2Dalign%3A%20center%3B%0A%7D%0Aimg%20%7B%0Abackground%2Dcolor%3A%20%23FFFFFF%3B%0Apadding%3A%202px%3B%0Aborder%3A%201px%20solid%20%23DDDDDD%3B%0Aborder%2Dradius%3A%203px%3B%0Aborder%3A%201px%20solid%20%23CCCCCC%3B%0Amargin%3A%200%205px%3B%0A%7D%0Ah1%20%7B%0Amargin%2Dtop%3A%200%3B%0Afont%2Dsize%3A%2035px%3B%0Aline%2Dheight%3A%2040px%3B%0A%7D%0Ah2%20%7B%0Aborder%2Dbottom%3A%204px%20solid%20%23f7f7f7%3B%0Apadding%2Dtop%3A%2010px%3B%0Apadding%2Dbottom%3A%202px%3B%0Afont%2Dsize%3A%20145%25%3B%0A%7D%0Ah3%20%7B%0Aborder%2Dbottom%3A%202px%20solid%20%23f7f7f7%3B%0Apadding%2Dtop%3A%2010px%3B%0Afont%2Dsize%3A%20120%25%3B%0A%7D%0Ah4%20%7B%0Aborder%2Dbottom%3A%201px%20solid%20%23f7f7f7%3B%0Amargin%2Dleft%3A%208px%3B%0Afont%2Dsize%3A%20105%25%3B%0A%7D%0Ah5%2C%20h6%20%7B%0Aborder%2Dbottom%3A%201px%20solid%20%23ccc%3B%0Afont%2Dsize%3A%20105%25%3B%0A%7D%0Aa%20%7B%0Acolor%3A%20%230033dd%3B%0Atext%2Ddecoration%3A%20none%3B%0A%7D%0Aa%3Ahover%20%7B%0Acolor%3A%20%236666ff%3B%20%7D%0Aa%3Avisited%20%7B%0Acolor%3A%20%23800080%3B%20%7D%0Aa%3Avisited%3Ahover%20%7B%0Acolor%3A%20%23BB00BB%3B%20%7D%0Aa%5Bhref%5E%3D%22http%3A%22%5D%20%7B%0Atext%2Ddecoration%3A%20underline%3B%20%7D%0Aa%5Bhref%5E%3D%22https%3A%22%5D%20%7B%0Atext%2Ddecoration%3A%20underline%3B%20%7D%0A%0Acode%20%3E%20span%2Ekw%20%7B%20color%3A%20%23555%3B%20font%2Dweight%3A%20bold%3B%20%7D%20%0Acode%20%3E%20span%2Edt%20%7B%20color%3A%20%23902000%3B%20%7D%20%0Acode%20%3E%20span%2Edv%20%7B%20color%3A%20%2340a070%3B%20%7D%20%0Acode%20%3E%20span%2Ebn%20%7B%20color%3A%20%23d14%3B%20%7D%20%0Acode%20%3E%20span%2Efl%20%7B%20color%3A%20%23d14%3B%20%7D%20%0Acode%20%3E%20span%2Ech%20%7B%20color%3A%20%23d14%3B%20%7D%20%0Acode%20%3E%20span%2Est%20%7B%20color%3A%20%23d14%3B%20%7D%20%0Acode%20%3E%20span%2Eco%20%7B%20color%3A%20%23888888%3B%20font%2Dstyle%3A%20italic%3B%20%7D%20%0Acode%20%3E%20span%2Eot%20%7B%20color%3A%20%23007020%3B%20%7D%20%0Acode%20%3E%20span%2Eal%20%7B%20color%3A%20%23ff0000%3B%20font%2Dweight%3A%20bold%3B%20%7D%20%0Acode%20%3E%20span%2Efu%20%7B%20color%3A%20%23900%3B%20font%2Dweight%3A%20bold%3B%20%7D%20%0Acode%20%3E%20span%2Eer%20%7B%20color%3A%20%23a61717%3B%20background%2Dcolor%3A%20%23e3d2d2%3B%20%7D%20%0A" type="text/css" />
</head>
<body>
<h1 class="title toc-ignore">r2ogs6 Developer Guide</h1>
<h4 class="author">Ruben Heinrich</h4>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a><span class="fu">library</span>(r2ogs6)</span></code></pre></div>
<div id="hi-there" class="section level2">
<h2>Hi there!</h2>
<p>Welcome to my dev guide on <code>r2ogs6</code>. This is a collection of tips, useful info (and admittedly a few warnings) which will hopefully make your life a bit easier when developing this package.</p>
</div>
<div id="the-basics" class="section level2">
<h2>The basics</h2>
<p>Before we dive into any implementation details, we will take a look at how exactly this package is structured first. <code>r2ogs6</code> was developed using the workflow described <a href="https://r-pkgs.org/index.html">here</a>. I strongly recommend keeping it that way as it will save you time and headaches.</p>
<p></p>
<p>In the main folder <code>R/</code> you will find a lot of scripts, most of which can be grouped into the following categories:</p>
<ul>
<li><p><code>export_*.R</code> export functions</p></li>
<li><p><code>generate_*.R</code> code generation</p></li>
<li><p><code>read_in_*.R</code> import functions</p></li>
<li><p><code>ogs6_*.R</code> simulation class definitions</p></li>
<li><p><code>prj_*.R</code> class definitions for XML tags found in a <code>.prj</code> file</p></li>
<li><p><code>*_utils.R</code> utility functions used in multiple scripts</p></li>
</ul>
</div>
<div id="the-classes" class="section level2">
<h2>The classes</h2>
<p><code>r2ogs6</code> is largely built on top of S3 classes at the moment. For reasons I will elaborate on later, it is very viable to switch to R6 classes. But let’s look at what we have first.</p>
<p>….</p>
</div>
<div id="generating-new-classes" class="section level2">
<h2>Generating new classes</h2>
<p>If you’ve familiarized yourself with OpenGeoSys 6, you know that there are a lot, and by a lot I mean a LOT of parameters and special cases regarding the <code>.prj</code> XML tags. For a nice new class based on such a tag, you will have to consider all of them.</p>
<p>To save me (and you) a bit of typing, I’ve written a few useful functions for this.</p>
<div id="analyse_xml" class="section level3">
<h3>analyse_xml()</h3>
<p>The first and arguably most important one is <code>analyse_xml()</code>. It matches files in a folder, reads them in as XML and searches for XML elements of a given name. It then analyses those elements and returns useful information about them, namely the names of their attributes and child elements. It prints a summary of its findings and also returns a list which we will look at in a moment.</p>
<p>I used this function for two things: Analysing … . Secondly, as soon as I had decided which tags should be represented by a class, I used the function output for class generation.</p>
</div>
<div id="generate_" class="section level3">
<h3>generate_*()</h3>
<p>So say we have some <code>.prj</code> files stored in a folder. I will show the workflow on a small dataset (that is, on a folder with only two <code>.prj</code> files) here, the path I usually passed to <code>analyse_xml()</code> was the directory containing all of the benchmark files for OpenGeoSys 6 which can be downloaded from <a href="https://gitlab.opengeosys.org/ogs/ogs/-/tree/master/Tests/Data/">here</a>.</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>test_folder <span class="ot">&lt;-</span> <span class="fu">system.file</span>(<span class="st">&quot;extdata/vignettes_data/analyse_xml_demo&quot;</span>, </span>
<span id="cb2-2"><a href="#cb2-2" aria-hidden="true" tabindex="-1"></a> <span class="at">package =</span> <span class="st">&quot;r2ogs6&quot;</span>)</span></code></pre></div>
<p>Now say we have decided we are going to make a class based on the element with tag name <code>nonlinear_solver</code>. For readability reasons, I will store the results of <code>analyse_xml()</code> in a variable and pass it to our generator function. If you want, you can skip this step and call <code>analyse_xml()</code> in the generator function directly.</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb3-1"><a href="#cb3-1" aria-hidden="true" tabindex="-1"></a>analysis_results <span class="ot">&lt;-</span> <span class="fu">analyse_xml</span>(<span class="at">path =</span> test_folder,</span>
<span id="cb3-2"><a href="#cb3-2" aria-hidden="true" tabindex="-1"></a> <span class="at">pattern =</span> <span class="st">&quot;</span><span class="sc">\\</span><span class="st">.prj$&quot;</span>,</span>
<span id="cb3-3"><a href="#cb3-3" aria-hidden="true" tabindex="-1"></a> <span class="at">xpath =</span> <span class="st">&quot;//nonlinear_solver&quot;</span>,</span>
<span id="cb3-4"><a href="#cb3-4" aria-hidden="true" tabindex="-1"></a> <span class="at">print_findings =</span> <span class="cn">TRUE</span>)</span>
<span id="cb3-5"><a href="#cb3-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb3-6"><a href="#cb3-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; I parsed 2 valid XML files matching your pattern.</span></span>
<span id="cb3-7"><a href="#cb3-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb3-8"><a href="#cb3-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; I found at least one element named nonlinear_solver in the following file(s):</span></span>
<span id="cb3-9"><a href="#cb3-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; beam.prj </span></span>
<span id="cb3-10"><a href="#cb3-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; beam3d.prj </span></span>
<span id="cb3-11"><a href="#cb3-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb3-12"><a href="#cb3-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; In total, I found 5 element(s) named nonlinear_solver.</span></span>
<span id="cb3-13"><a href="#cb3-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb3-14"><a href="#cb3-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; These are the child elements I found:</span></span>
<span id="cb3-15"><a href="#cb3-15" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; name ex_occ p_occ total total_mean</span></span>
<span id="cb3-16"><a href="#cb3-16" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 1 name 2 0.4 2 0.4</span></span>
<span id="cb3-17"><a href="#cb3-17" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 2 type 2 0.4 2 0.4</span></span>
<span id="cb3-18"><a href="#cb3-18" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 3 max_iter 2 0.4 2 0.4</span></span>
<span id="cb3-19"><a href="#cb3-19" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 4 linear_solver 2 0.4 2 0.4</span></span>
<span id="cb3-20"><a href="#cb3-20" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 5 maximum_iterations 1 0.2 1 0.2</span></span>
<span id="cb3-21"><a href="#cb3-21" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 6 error_tolerance 1 0.2 1 0.2</span></span>
<span id="cb3-22"><a href="#cb3-22" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 7 damping 1 0.2 1 0.2</span></span></code></pre></div>
<p>First, I define my path and specify that only files with the ending <code>.prj</code> will be parsed. I’m looking for elements named <code>nonlinear_solver</code>, and I’m looking for them in the whole document. This often isn’t the best option since sometimes nodes may have the same name but contain different things depending on their exact position in the document, which is also the case here. To narrow it down further, change <code>xpath</code> accordingly.</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb4-1"><a href="#cb4-1" aria-hidden="true" tabindex="-1"></a>analysis_results <span class="ot">&lt;-</span> <span class="fu">analyse_xml</span>(<span class="at">path =</span> test_folder,</span>
<span id="cb4-2"><a href="#cb4-2" aria-hidden="true" tabindex="-1"></a> <span class="at">pattern =</span> <span class="st">&quot;</span><span class="sc">\\</span><span class="st">.prj$&quot;</span>,</span>
<span id="cb4-3"><a href="#cb4-3" aria-hidden="true" tabindex="-1"></a> <span class="at">xpath =</span> <span class="st">&quot;/OpenGeoSysProject/nonlinear_solvers/nonlinear_solver&quot;</span>,</span>
<span id="cb4-4"><a href="#cb4-4" aria-hidden="true" tabindex="-1"></a> <span class="at">print_findings =</span> <span class="cn">TRUE</span>)</span>
<span id="cb4-5"><a href="#cb4-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb4-6"><a href="#cb4-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; I parsed 2 valid XML files matching your pattern.</span></span>
<span id="cb4-7"><a href="#cb4-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb4-8"><a href="#cb4-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; I found at least one element named nonlinear_solver in the following file(s):</span></span>
<span id="cb4-9"><a href="#cb4-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; beam.prj </span></span>
<span id="cb4-10"><a href="#cb4-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; beam3d.prj </span></span>
<span id="cb4-11"><a href="#cb4-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb4-12"><a href="#cb4-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; In total, I found 2 element(s) named nonlinear_solver.</span></span>
<span id="cb4-13"><a href="#cb4-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb4-14"><a href="#cb4-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; These are the child elements I found:</span></span>
<span id="cb4-15"><a href="#cb4-15" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; name ex_occ p_occ total total_mean</span></span>
<span id="cb4-16"><a href="#cb4-16" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 1 name 2 1.0 2 1.0</span></span>
<span id="cb4-17"><a href="#cb4-17" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 2 type 2 1.0 2 1.0</span></span>
<span id="cb4-18"><a href="#cb4-18" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 3 max_iter 2 1.0 2 1.0</span></span>
<span id="cb4-19"><a href="#cb4-19" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 4 linear_solver 2 1.0 2 1.0</span></span>
<span id="cb4-20"><a href="#cb4-20" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; 5 damping 1 0.5 1 0.5</span></span></code></pre></div>
<p>Now we can be sure our future class will be generated from the correct parameters. <code>analyse_xml()</code> returns a named list invisibly, let’s have a short look at it.</p>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb5-1"><a href="#cb5-1" aria-hidden="true" tabindex="-1"></a>analysis_results</span>
<span id="cb5-2"><a href="#cb5-2" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; $xpath</span></span>
<span id="cb5-3"><a href="#cb5-3" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; [1] &quot;/OpenGeoSysProject/nonlinear_solvers/nonlinear_solver&quot;</span></span>
<span id="cb5-4"><a href="#cb5-4" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb5-5"><a href="#cb5-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; $children</span></span>
<span id="cb5-6"><a href="#cb5-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; name type max_iter linear_solver damping </span></span>
<span id="cb5-7"><a href="#cb5-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; TRUE TRUE TRUE TRUE FALSE </span></span>
<span id="cb5-8"><a href="#cb5-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb5-9"><a href="#cb5-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; $attributes</span></span>
<span id="cb5-10"><a href="#cb5-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; logical(0)</span></span>
<span id="cb5-11"><a href="#cb5-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb5-12"><a href="#cb5-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; $both_sorted</span></span>
<span id="cb5-13"><a href="#cb5-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; name type max_iter linear_solver damping </span></span>
<span id="cb5-14"><a href="#cb5-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; TRUE TRUE TRUE TRUE FALSE</span></span></code></pre></div>
<p>You can see the list contains the <code>xpath</code> parameter passed to <code>analyse_xml()</code>, along with three named logical vectors called <code>children</code>, <code>attributes</code> and <code>both_sorted</code> respectively. They can be read like this: If an attribute or a child of the element specified by <code>xpath</code> always occurred, it is a required parameter for the new class. Else, it is an optional parameter. The logical vectors are sorted by occurrency, so the rarest children and attributes will go to the very end of their logical vector. Now, let’s generate some code!</p>
<p>For S3 classes, we generate a constructor like this:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb6-1"><a href="#cb6-1" aria-hidden="true" tabindex="-1"></a><span class="fu">generate_constructor</span>(<span class="at">params =</span> analysis_results,</span>
<span id="cb6-2"><a href="#cb6-2" aria-hidden="true" tabindex="-1"></a> <span class="at">print_result =</span> <span class="cn">TRUE</span>)</span>
<span id="cb6-3"><a href="#cb6-3" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; new_prj_nonlinear_solver &lt;- function(name,</span></span>
<span id="cb6-4"><a href="#cb6-4" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type,</span></span>
<span id="cb6-5"><a href="#cb6-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter,</span></span>
<span id="cb6-6"><a href="#cb6-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver,</span></span>
<span id="cb6-7"><a href="#cb6-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping = NULL) {</span></span>
<span id="cb6-8"><a href="#cb6-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; structure(list(name = name,</span></span>
<span id="cb6-9"><a href="#cb6-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type = type,</span></span>
<span id="cb6-10"><a href="#cb6-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter = max_iter,</span></span>
<span id="cb6-11"><a href="#cb6-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver = linear_solver,</span></span>
<span id="cb6-12"><a href="#cb6-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping = damping,</span></span>
<span id="cb6-13"><a href="#cb6-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; xpath = &quot;nonlinear_solvers/nonlinear_solver&quot;,</span></span>
<span id="cb6-14"><a href="#cb6-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; attr_names = c(),</span></span>
<span id="cb6-15"><a href="#cb6-15" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; flatten_on_exp = character()</span></span>
<span id="cb6-16"><a href="#cb6-16" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; ),</span></span>
<span id="cb6-17"><a href="#cb6-17" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; class = &quot;prj_nonlinear_solver&quot;</span></span>
<span id="cb6-18"><a href="#cb6-18" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; )</span></span>
<span id="cb6-19"><a href="#cb6-19" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb6-20"><a href="#cb6-20" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span></code></pre></div>
<p>For S3 classes, we generate a helper like this:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb7-1"><a href="#cb7-1" aria-hidden="true" tabindex="-1"></a><span class="fu">generate_helper</span>(<span class="at">params =</span> analysis_results,</span>
<span id="cb7-2"><a href="#cb7-2" aria-hidden="true" tabindex="-1"></a> <span class="at">print_result =</span> <span class="cn">TRUE</span>)</span>
<span id="cb7-3"><a href="#cb7-3" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;prj_nonlinear_solver</span></span>
<span id="cb7-4"><a href="#cb7-4" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@description tag: nonlinear_solver</span></span>
<span id="cb7-5"><a href="#cb7-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param name</span></span>
<span id="cb7-6"><a href="#cb7-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param type</span></span>
<span id="cb7-7"><a href="#cb7-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param max_iter</span></span>
<span id="cb7-8"><a href="#cb7-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param linear_solver</span></span>
<span id="cb7-9"><a href="#cb7-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param damping Optional: </span></span>
<span id="cb7-10"><a href="#cb7-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@export</span></span>
<span id="cb7-11"><a href="#cb7-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; prj_nonlinear_solver &lt;- function(name,</span></span>
<span id="cb7-12"><a href="#cb7-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type,</span></span>
<span id="cb7-13"><a href="#cb7-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter,</span></span>
<span id="cb7-14"><a href="#cb7-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver,</span></span>
<span id="cb7-15"><a href="#cb7-15" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping = NULL) {</span></span>
<span id="cb7-16"><a href="#cb7-16" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb7-17"><a href="#cb7-17" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; # Add coercing utility here</span></span>
<span id="cb7-18"><a href="#cb7-18" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb7-19"><a href="#cb7-19" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; new_prj_nonlinear_solver(name,</span></span>
<span id="cb7-20"><a href="#cb7-20" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type,</span></span>
<span id="cb7-21"><a href="#cb7-21" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter,</span></span>
<span id="cb7-22"><a href="#cb7-22" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver,</span></span>
<span id="cb7-23"><a href="#cb7-23" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping)</span></span>
<span id="cb7-24"><a href="#cb7-24" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb7-25"><a href="#cb7-25" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span></code></pre></div>
<p>For R6 classes, we generate a constructor like this:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb8-1"><a href="#cb8-1" aria-hidden="true" tabindex="-1"></a><span class="fu">generate_R6</span>(<span class="at">params =</span> analysis_results,</span>
<span id="cb8-2"><a href="#cb8-2" aria-hidden="true" tabindex="-1"></a> <span class="at">print_result =</span> <span class="cn">TRUE</span>)</span>
<span id="cb8-3"><a href="#cb8-3" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; OGS6_nonlinear_solver &lt;- R6::R6Class(&quot;OGS6_nonlinear_solver&quot;,</span></span>
<span id="cb8-4"><a href="#cb8-4" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; public = list(</span></span>
<span id="cb8-5"><a href="#cb8-5" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@description</span></span>
<span id="cb8-6"><a href="#cb8-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Creates new OGS6_nonlinear_solverobject</span></span>
<span id="cb8-7"><a href="#cb8-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param name</span></span>
<span id="cb8-8"><a href="#cb8-8" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param type</span></span>
<span id="cb8-9"><a href="#cb8-9" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param max_iter</span></span>
<span id="cb8-10"><a href="#cb8-10" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param linear_solver</span></span>
<span id="cb8-11"><a href="#cb8-11" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@param damping Optional: initialize = function(name,</span></span>
<span id="cb8-12"><a href="#cb8-12" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type,</span></span>
<span id="cb8-13"><a href="#cb8-13" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter,</span></span>
<span id="cb8-14"><a href="#cb8-14" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver,</span></span>
<span id="cb8-15"><a href="#cb8-15" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping = NULL){</span></span>
<span id="cb8-16"><a href="#cb8-16" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; self$name &lt;- name</span></span>
<span id="cb8-17"><a href="#cb8-17" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; self$type &lt;- type</span></span>
<span id="cb8-18"><a href="#cb8-18" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; self$max_iter &lt;- max_iter</span></span>
<span id="cb8-19"><a href="#cb8-19" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; self$linear_solver &lt;- linear_solver</span></span>
<span id="cb8-20"><a href="#cb8-20" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; self$damping &lt;- damping</span></span>
<span id="cb8-21"><a href="#cb8-21" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-22"><a href="#cb8-22" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; ),</span></span>
<span id="cb8-23"><a href="#cb8-23" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-24"><a href="#cb8-24" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; active = list(</span></span>
<span id="cb8-25"><a href="#cb8-25" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field name</span></span>
<span id="cb8-26"><a href="#cb8-26" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.name&#39;</span></span>
<span id="cb8-27"><a href="#cb8-27" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; name = function(value) {</span></span>
<span id="cb8-28"><a href="#cb8-28" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; if(missing(value)) {</span></span>
<span id="cb8-29"><a href="#cb8-29" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.name</span></span>
<span id="cb8-30"><a href="#cb8-30" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }else{</span></span>
<span id="cb8-31"><a href="#cb8-31" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.name &lt;- value</span></span>
<span id="cb8-32"><a href="#cb8-32" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-33"><a href="#cb8-33" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-34"><a href="#cb8-34" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-35"><a href="#cb8-35" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field type</span></span>
<span id="cb8-36"><a href="#cb8-36" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.type&#39;</span></span>
<span id="cb8-37"><a href="#cb8-37" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; type = function(value) {</span></span>
<span id="cb8-38"><a href="#cb8-38" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; if(missing(value)) {</span></span>
<span id="cb8-39"><a href="#cb8-39" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.type</span></span>
<span id="cb8-40"><a href="#cb8-40" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }else{</span></span>
<span id="cb8-41"><a href="#cb8-41" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.type &lt;- value</span></span>
<span id="cb8-42"><a href="#cb8-42" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-43"><a href="#cb8-43" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-44"><a href="#cb8-44" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-45"><a href="#cb8-45" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field max_iter</span></span>
<span id="cb8-46"><a href="#cb8-46" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.max_iter&#39;</span></span>
<span id="cb8-47"><a href="#cb8-47" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; max_iter = function(value) {</span></span>
<span id="cb8-48"><a href="#cb8-48" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; if(missing(value)) {</span></span>
<span id="cb8-49"><a href="#cb8-49" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.max_iter</span></span>
<span id="cb8-50"><a href="#cb8-50" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }else{</span></span>
<span id="cb8-51"><a href="#cb8-51" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.max_iter &lt;- value</span></span>
<span id="cb8-52"><a href="#cb8-52" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-53"><a href="#cb8-53" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-54"><a href="#cb8-54" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-55"><a href="#cb8-55" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field linear_solver</span></span>
<span id="cb8-56"><a href="#cb8-56" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.linear_solver&#39;</span></span>
<span id="cb8-57"><a href="#cb8-57" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; linear_solver = function(value) {</span></span>
<span id="cb8-58"><a href="#cb8-58" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; if(missing(value)) {</span></span>
<span id="cb8-59"><a href="#cb8-59" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.linear_solver</span></span>
<span id="cb8-60"><a href="#cb8-60" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }else{</span></span>
<span id="cb8-61"><a href="#cb8-61" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.linear_solver &lt;- value</span></span>
<span id="cb8-62"><a href="#cb8-62" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-63"><a href="#cb8-63" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-64"><a href="#cb8-64" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-65"><a href="#cb8-65" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field damping</span></span>
<span id="cb8-66"><a href="#cb8-66" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.damping&#39;</span></span>
<span id="cb8-67"><a href="#cb8-67" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; damping = function(value) {</span></span>
<span id="cb8-68"><a href="#cb8-68" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; if(missing(value)) {</span></span>
<span id="cb8-69"><a href="#cb8-69" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.damping</span></span>
<span id="cb8-70"><a href="#cb8-70" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }else{</span></span>
<span id="cb8-71"><a href="#cb8-71" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.damping &lt;- value</span></span>
<span id="cb8-72"><a href="#cb8-72" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-73"><a href="#cb8-73" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-74"><a href="#cb8-74" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-75"><a href="#cb8-75" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field is_subclass</span></span>
<span id="cb8-76"><a href="#cb8-76" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.is_subclass&#39;</span></span>
<span id="cb8-77"><a href="#cb8-77" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; is_subclass = function() {</span></span>
<span id="cb8-78"><a href="#cb8-78" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.is_subclass</span></span>
<span id="cb8-79"><a href="#cb8-79" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-80"><a href="#cb8-80" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-81"><a href="#cb8-81" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field subclasses_names</span></span>
<span id="cb8-82"><a href="#cb8-82" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.subclasses_names&#39;</span></span>
<span id="cb8-83"><a href="#cb8-83" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; subclasses_names = function() {</span></span>
<span id="cb8-84"><a href="#cb8-84" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.subclasses_names</span></span>
<span id="cb8-85"><a href="#cb8-85" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; },</span></span>
<span id="cb8-86"><a href="#cb8-86" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-87"><a href="#cb8-87" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;@field attr_names</span></span>
<span id="cb8-88"><a href="#cb8-88" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; #&#39;Access to private parameter &#39;.attr_names&#39;</span></span>
<span id="cb8-89"><a href="#cb8-89" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; attr_names = function() {</span></span>
<span id="cb8-90"><a href="#cb8-90" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private$.attr_names</span></span>
<span id="cb8-91"><a href="#cb8-91" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; }</span></span>
<span id="cb8-92"><a href="#cb8-92" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; ),</span></span>
<span id="cb8-93"><a href="#cb8-93" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; </span></span>
<span id="cb8-94"><a href="#cb8-94" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; private = list(</span></span>
<span id="cb8-95"><a href="#cb8-95" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .name = NULL,</span></span>
<span id="cb8-96"><a href="#cb8-96" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .type = NULL,</span></span>
<span id="cb8-97"><a href="#cb8-97" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .max_iter = NULL,</span></span>
<span id="cb8-98"><a href="#cb8-98" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .linear_solver = NULL,</span></span>
<span id="cb8-99"><a href="#cb8-99" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .damping = NULL,</span></span>
<span id="cb8-100"><a href="#cb8-100" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .is_subclass = TRUE,</span></span>
<span id="cb8-101"><a href="#cb8-101" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .subclasses_names = character(),</span></span>
<span id="cb8-102"><a href="#cb8-102" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; .attr_names = c(),</span></span>
<span id="cb8-103"><a href="#cb8-103" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; )</span></span>
<span id="cb8-104"><a href="#cb8-104" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; )</span></span></code></pre></div>
<p>Ta-daa, you now have some nice stubs. Copy them into a script in the <code>R</code> folder of this package, add some documentation and validation to it and you’re almost done.</p>
</div>
</div>
<div id="integrating-new-classes" class="section level2">
<h2>Integrating new classes</h2>
<p>Now that we have a class, we need to tell the package it exists. This is so when we’re reading in or exporting a <code>.prj</code> file, it knows to automatically turn the content of our <code>nonlinear_solver</code> tag into an object of our new class and the other way around. To achieve this, execute the code in <code>data_raw/xpaths_for_classes.R</code>. What this will do is update the <code>xpaths_for_classes</code> parameter, adding an entry for your class. Afterwards, run <code>xpaths_for_classes[[&quot;your_class_name&quot;]]</code>. It should return the <code>xpath</code> parameter of your class like so:</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><span id="cb9-1"><a href="#cb9-1" aria-hidden="true" tabindex="-1"></a>xpaths_for_classes[[<span class="st">&quot;prj_process&quot;</span>]]</span>
<span id="cb9-2"><a href="#cb9-2" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; [1] &quot;processes/process&quot;</span></span>
<span id="cb9-3"><a href="#cb9-3" aria-hidden="true" tabindex="-1"></a></span>
<span id="cb9-4"><a href="#cb9-4" aria-hidden="true" tabindex="-1"></a><span class="co"># A class can have multiple xpaths if the represented node occurs at different positions.</span></span>
<span id="cb9-5"><a href="#cb9-5" aria-hidden="true" tabindex="-1"></a>xpaths_for_classes[[<span class="st">&quot;prj_convergence_criterion&quot;</span>]]</span>
<span id="cb9-6"><a href="#cb9-6" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; [1] &quot;time_loop/processes/process/convergence_criterion&quot; </span></span>
<span id="cb9-7"><a href="#cb9-7" aria-hidden="true" tabindex="-1"></a><span class="co">#&gt; [2] &quot;time_loop/global_process_coupling/convergence_criteria/convergence_criterion&quot;</span></span></code></pre></div>
<p>If the class you’ve created is a <code>.prj</code> top level class or a child of a top level wrapper node like <code>processes</code>, add a corresponding <code>OGS6</code> private parameter and an active field. For example, the <code>processes</code> node is represented as a list, so I added the private parameter <code>.processes = list()</code> and the active field <code>processes</code>.</p>
<p>A lot of things in the <code>r2ogs6</code> package work in a way that is a bit “meta”. Often times, functions are called via <code>eval(parse(text = call_string))</code> where <code>call_string</code> 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.</p>
<p>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.</p>
</div>
<div id="recursive-function-guide" class="section level2">
<h2>Recursive function guide</h2>
<p>If that wasn’t it, I’m afraid you might have to take a look at the functions handling import, export and benchmark script generation. These are a bit tricky because they use recursion which so far has proven to be efficient structure-wise but not exactly fun to think about.</p>
<div id="read_in" class="section level3">
<h3>read_in</h3>
</div>
<div id="to_node" class="section level3">
<h3>to_node</h3>
</div>
<div id="generate_benchmark_script" class="section level3">
<h3>generate_benchmark_script</h3>
</div>
</div>
<div id="conclusion" class="section level2">
<h2>Conclusion</h2>
<p>I hope you’ve taken away some helpful information from this short guide. If you make changes to improve the workflow, please update this vignette for the next dev!</p>
</div>
<!-- code folding -->
<!-- dynamically load mathjax for compatibility with self-contained -->
<script>
(function () {
var script = document.createElement("script");
script.type = "text/javascript";
script.src = "https://mathjax.rstudio.com/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML";
document.getElementsByTagName("head")[0].appendChild(script);
})();
</script>
</body>
</html>
Source diff could not be displayed: it is too large. Options to address this: view the blob.
Source diff could not be displayed: it is too large. Options to address this: view the blob.
---
title: "r2ogs6 Ensemble Guide"
author: "Ruben Heinrich"
#output: pdf_document
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{r2ogs6 Ensemble Guide}
......@@ -18,6 +17,11 @@ knitr::opts_chunk$set(
comment = "#>",
message = FALSE
)
# the python library vtk needs an explicit import statement for knitting
vtk <- reticulate::import("vtk")
dsa <- reticulate::import("vtk.numpy_interface.dataset_adapter")
devtools::load_all(".")
```
```{r setup}
......@@ -60,13 +64,13 @@ testdir_path <- tempdir()
sim_path <- paste0(testdir_path, "/axisym_theis_sim")
ogs6_obj <- OGS6$new(sim_name = "axisym_theis",
sim_path = "D:/ogs6_theis/axisym_theis_sim")
sim_path = sim_path)
# Change this to fit your system
prj_path <- system.file("extdata/benchmarks/AxiSymTheis/",
"axisym_theis.prj", package = "r2ogs6")
read_in_prj(ogs6_obj, prj_path)
read_in_prj(ogs6_obj, prj_path, read_in_gml = T)
```
......@@ -89,11 +93,11 @@ ogs6_ens <-
Now you can start the simulation.
```{r, eval = FALSE}
```{r results='hide'}
ogs6_ens$run_simulation()
```
```{r, include = FALSE}
```{r, results='hide'}
lapply(ogs6_ens$ensemble, ogs6_read_output_files)
```
......@@ -188,11 +192,11 @@ ogs6_ens_big <-
Now you can start the simulation.
```{r, eval = FALSE}
```{r results='hide'}
ogs6_ens_big$run_simulation()
```
```{r, include = FALSE}
```{r results='hide'}
lapply(ogs6_ens_big$ensemble, ogs6_read_output_files)
```
......@@ -241,7 +245,7 @@ log_vals <- vapply(percentages, function(x){
back_transf_vals <- 10^log_vals
# Change sim_path to fit your system
ogs6_obj$sim_path <- "D:/ogs6_theis/axisym_theis_sim_log_storage"
ogs6_obj$sim_path <- paste0(testdir_path, "/axisym_theis_sim_log_storage")
# Set up new ensemble
ogs6_ens_sto <-
......@@ -260,11 +264,11 @@ ogs6_ens_sto <-
As before, we can run the simulation right away.
```{r, eval = FALSE}
```{r results='hide'}
ogs6_ens_sto$run_simulation()
```
```{r, include = FALSE}
```{r results='hide'}
lapply(ogs6_ens_sto$ensemble, ogs6_read_output_files)
```
......@@ -311,13 +315,13 @@ First, we create a simulation object to base our ensemble on and read in the `.p
sim_path <- paste0(testdir_path, "/theis_sim")
ogs6_obj <- OGS6$new(sim_name = "theis",
sim_path = "D:/ogs6_theis/theis_sim")
sim_path = sim_path)
# Change this to fit your system
prj_path <- system.file("extdata/benchmarks/theis_well_pumping/",
"theis.prj", package = "r2ogs6")
read_in_prj(ogs6_obj, prj_path)
read_in_prj(ogs6_obj, prj_path, read_in_gml = T)
# Increase each_steps
ogs6_obj$time_loop$output$timesteps$pair$each_steps <- 200
......@@ -348,11 +352,11 @@ ogs6_ens_theis_2 <-
Now you can start the simulation.
```{r, eval = FALSE}
```{r results='hide'}
ogs6_ens_theis_2$run_simulation()
```
```{r, include = FALSE}
```{r results='hide'}
lapply(ogs6_ens_theis_2$ensemble, ogs6_read_output_files)
```
......@@ -433,7 +437,7 @@ log_vals <- vapply(percentages, function(x){
back_transf_vals <- 10^log_vals
# Change sim_path to fit your system
ogs6_obj$sim_path <- "D:/ogs6_theis/theis_sim_log_slope"
ogs6_obj$sim_path <- paste0(testdir_path, "/theis_sim_log_slope")
# Set up new ensemble
ogs6_ens_slo <-
......@@ -452,11 +456,11 @@ ogs6_ens_slo <-
As before, we can run the simulation right away.
```{r, eval = FALSE}
```{r results='hide'}
ogs6_ens_slo$run_simulation()
```
```{r, include = FALSE}
```{r results='hide'}
lapply(ogs6_ens_slo$ensemble, ogs6_read_output_files)
```
......
---
title: "r2ogs6 User Guide"
author: "Ruben Heinrich"
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{r2ogs6 User Guide}
%\VignetteEngine{knitr::rmarkdown}
%\VignetteEncoding{UTF-8}
output: html_document
#output: rmarkdown::html_vignette
#vignette: >
# %\VignetteIndexEntry{r2ogs6 User Guide}
# %\VignetteEngine{knitr::rmarkdown}
# %\VignetteEncoding{UTF-8}
---
```{r, include = FALSE}
knitr::opts_chunk$set(
eval = nzchar(Sys.getenv("r2ogs6_ensemble_guide_eval")),
collapse = TRUE,
comment = "#>"
)
)
# the python library vtk needs an explicit import statement for knitting
vtk <- reticulate::import("vtk")
dsa <- reticulate::import("vtk.numpy_interface.dataset_adapter")
devtools::load_all(".")
```
......@@ -42,9 +47,9 @@ To represent a simulation object, `r2ogs6` uses an `R6` class called `OGS6`. If
```{r}
# Change this to fit your system
sim_path <- system.file("extdata/benchmarks/flow_no_strain",
package = "r2ogs6")
# sim_path <- system.file("extdata/benchmarks/flow_no_strain",
# package = "r2ogs6")
sim_path <- tempdir()
ogs6_obj <- OGS6$new(sim_name = "my_simulation",
sim_path = sim_path)
```
......@@ -66,8 +71,9 @@ For demonstration purposes, I will use a project from the `HydroMechanics` bench
```{r}
# Change this to fit your system
prj_path <- paste0(sim_path, "/flow_no_strain.prj")
read_in_prj(ogs6_obj, prj_path = prj_path)
prj_path <- system.file("extdata/benchmarks/flow_no_strain/flow_no_strain.prj",
package = "r2ogs6")
read_in_prj(ogs6_obj, prj_path = prj_path, read_in_gml = T)
```
......@@ -86,7 +92,7 @@ ogs6_obj$get_status()
Since we haven't defined anything so far, you'll see a lot of red there. But the results gave us a hint what we can add. We'll go from there and try to find out more about the possible input data. Say we want to find out more about `process` objects.
```r
```{r}
# To take a look at the documentation, use ? followed by the name of a class
?prj_process
```
......@@ -128,33 +134,143 @@ Since I already read in a `.prj` file earlier, I won't run the above snippet. If
As soon as we've added all necessary parameters, we can try starting our simulation. This will run a few additional checks and then start OpenGeoSys 6. If `write_logfile` is set to `FALSE`, the output from OpenGeoSys 6 will be shown on the console.
```{r eval = FALSE}
```{r results='hide'}
ogs6_run_simulation(ogs6_obj, write_logfile = TRUE)
```
## Retrieve the results
After our simulation is finished, we might want to plot some results. But how do we retrieve them? If all went as expected, we don't need to call an extra function for that because `ogs6_run_simulation()` already calls `ogs6_read_output_files()` internally. We only need to decide what information we want to extract. Say we're interested in the `pressure` Parameter from the last timestep. For this easy example, only one `.pvd` file was produced.
```{r include = FALSE}
```{r include = T}
ogs6_read_output_files(ogs6_obj)
```
## Retrieve the results
After our simulation is finished, we might want to plot some results. But how do we retrieve them? If all went as expected, we don't need to call an extra function for that because `ogs6_run_simulation()` already calls `ogs6_read_output_files()` internally. We only need to decide what information we want to extract. Say we're interested in the `pressure` Parameter from the last timestep. For this easy example, only one `.pvd` file was produced.
```{r}
```{r fig.width=5}
# Extract relevant info into dataframe
result_df <- ogs6_obj$pvds[[1]]$get_point_data(keys = c("pressure"))
result_df <- result_df[(result_df$timestep!=0),]
# Plot results
ggplot(result_df,
aes(x = x,
y = pressure)) +
y = y,
color = pressure)) +
geom_point() +
#geom_raster(interpolate = T)+
#geom_contour_filled()+
xlab("x coordinate") +
ylab("pressure")
ylab("y coordinate") +
theme_bw()
```
## Running multiple simulations
If we want to run not one but multiple simulations, we can use the simulation object we just created as a blueprint for an ensemble run. The workflow for this is described in detail [here](ensemble_workflow_vignette.Rmd).
## Benchmark script generation
Another feature of `r2ogs6` is benchmark script generation. For this, there are
two functions.
- `ogs6_generate_benchmark_script()` creates an R script from a `.prj` file
- `ogs6_generate_benchmark_scripts()` is a wrapper for the former. Instead of a
single `.prj` file path, it takes a directory path as its argument.
Let's look at the parameters for `ogs6_generate_benchmark_script()` first. Say
we have a project file `sim_file.prj` we want to generate a script from.
```{r}
# The path to the project file you want to generate a script from
prj_path <- "your_path/sim_file.prj"
# The path you want to save the simulation files to
sim_path <- "your_sim_directory/"
# The path to your `ogs.exe` (if not already specified in `r2ogs6` options)
ogs6_bin_path <- "your_ogs6_bin_path/"
# The path you want your benchmark script to be saved to
script_path <- "your_script_directory/"
```
Now that we have defined our parameters, we can generate the benchmark script.
```{r eval=F}
ogs6_generate_benchmark_script(prj_path = prj_path,
sim_path = sim_path,
ogs6_bin_path = ogs6_bin_path,
script_path = script_path)
```
On the other hand, if we want to generate R scripts from multiple (or all)
benchmarks, we can use the wrapper function `ogs6_generate_benchmark_scripts()`.
Its parameters are basically the same, only this time we supply it with a
directory path instead of a `.prj` path to start from.
You can download the benchmarks (or the subfolder you need) from
[here](https://gitlab.opengeosys.org/ogs/ogs/-/tree/master/Tests/Data) and then
set `path` to their location on your system.
```{r}
# The path to the directory you want to generate R scripts from
path <- "your_benchmark_path/"
# The path you want to save the simulation files to
sim_path <- "your_sim_directory/"
# The path you want your benchmark scripts to be saved to
script_path <- "your_script_directory/"
# Optional: Use if you want to start from a specific `.prj` file
starting_from_prj_path <- ""
# Optional: Use if you want to skip specific `.prj` files
skip_prj_paths <- character()
# Optional: Use if you want to skip specific `.prj` files
skip_prj_paths <- character()
# Optional: Use if you want to restrict scripting to specific `.prj` files
only_prj_files <- character()
```
And we're set! Note that `ogs6_generate_benchmark_scripts()` will reconstruct
the structure of the folder your benchmarks are stored in, e. g. if there's a
file `path/a/file.prj`, you will find the corresponding R script in
`sim_path/a/file.R`.
```{r eval=F}
ogs6_generate_benchmark_scripts(path = path,
sim_path = sim_path,
script_path = script_path,
starting_from_prj_path = starting_from_prj_path,
skip_prj_paths = skip_prj_paths,
only_prj_files = only_prj_files)
```
With this, we can generate scripts from all benchmarks in a single call. Of
course you can modify `path` to your liking if you're only interested in
generating scripts from certain subfolders.
Furthermore, you can restrict the script generation to benchmarks that used as
test in OGS 6.
```{r eval=F}
# extract *.prj files that are used as tests
rel_testbm_paths <- get_benchmark_paths("path/to/ogs-source-code/ProcessLib/")
rel_testbm_paths <- sapply(rel_testbm_paths, basename)
ogs6_generate_benchmark_scripts(path = path,
sim_path = sim_path,
script_path = script_path,
only_prj_files = rel_testbm_paths)
```
NOTE: New benchmarks and `.prj` parameters are constantly being added to OGS6.
If a benchmark contains parameters that have not been added to `r2ogs6` yet, the
script generation functions will not work. If this is the case, they will be
skipped and the original error message will be displayed in the console.
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