# gWidgetsWWW2 GUI for mkin {{{1
# Copyright (C) 2013-2016,2018,2019 Johannes Ranke
# Portions of this file are copyright (C) 2013 Eurofins Regulatory AG, Switzerland
# Contact: jranke@uni-bremen.de
# This file is part of the R package gmkin
# gmkin is free software: you can redistribute it and/or modify it under the
# terms of the GNU General Public License as published by the Free Software
# Foundation, either version 3 of the License, or (at your option) any later
# version.
# This program is distributed in the hope that it will be useful, but WITHOUT
# ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
# FOR A PARTICULAR PURPOSE. See the GNU General Public License for more
# details.
# You should have received a copy of the GNU General Public License along with
# this program. If not, see
", capture.output(summary(ftmp)), "
", c(tmptext[1:5], "\n...\n"), "") visible(ds.e.import) <- TRUE } new_ds_from_csv_handler <- function(h, ...) { tmpd <- try(read.table(tmptextfile, skip = as.numeric(svalue(ds.e.up.skip)), dec = svalue(ds.e.up.dec), sep = switch(svalue(ds.e.up.sep), whitespace = "", ";" = ";", "," = ","), header = svalue(ds.e.up.header), stringsAsFactors = FALSE)) if(svalue(ds.e.up.widelong) == "wide") { tmpdl <- mkin_wide_to_long(tmpd, time = as.character(svalue(ds.e.up.wide.time))) tmpdl$name <- as.character(tmpdl$name) tmpdl$override <- NA tmpdl$err <- 1 } else { tmpdl <- data.frame( name = tmpd[[svalue(ds.e.up.long.name)]], time = tmpd[[svalue(ds.e.up.long.time)]], value = tmpd[[svalue(ds.e.up.long.value)]]) tmpderr <- tmpd[[svalue(ds.e.up.long.err)]] if (!is.null(tmpderr)) tmpdl$err <- tmpderr } if (class(tmpd) != "try-error") { ds.cur <<- mkinds$new( title = "New import", time_unit = "", unit = "", data = tmpdl) if (is.null(ds.cur$data$err)) ds.cur$data$err <<- 1 update_ds.df() update_ds_editor() svalue(right) <- 2 } else { galert("Uploading failed", parent = "w") } } # Update the dataset editor {{{3 update_ds_editor <- function() { svalue(ds.title.ge) <- ds.cur$title svalue(ds.e.st) <- paste(ds.cur$sampling_times, collapse = ", ") svalue(ds.e.stu) <- ds.cur$time_unit svalue(ds.e.obs) <- paste(ds.cur$observed, collapse = ", ") svalue(ds.e.obu) <- ds.cur$unit svalue(ds.e.rep) <- ds.cur$replicates ds.e.gdf[,] <- ds.cur$data ds.keep$call_Ext("enable") visible(ds.e.import) <- FALSE svalue(ds.e.up.text) <- "" } # Widget setup {{{2 # Line 1 with buttons {{{3 ds.e.buttons <- ggroup(cont = ds.editor, horizontal = TRUE) ds.e.new <- gbutton("New dataset", cont = ds.e.buttons, handler = new_dataset_handler) ds.copy <- gbutton("Copy dataset", cont = ds.e.buttons, handler = copy_dataset_handler, ext.args = list(disabled = TRUE)) ds.delete <- gbutton("Delete dataset", cont = ds.e.buttons, handler = delete_dataset_handler, ext.args = list(disabled = TRUE)) ds.keep <- gbutton("Keep changes", cont = ds.e.buttons, handler = keep_ds_changes_handler) ds.keep$call_Ext("disable") # Formlayout for meta data {{{3 ds.e.gfl <- gformlayout(cont = ds.editor) ds.title.ge <- gedit(label = "Dataset title", width = 60, cont = ds.e.gfl) addHandlerChanged(ds.title.ge, handler = function(h, ...) ds.keep$call_Ext("enable")) ds.e.st <- gedit(width = 60, label = "Sampling times", cont = ds.e.gfl) ds.e.stu <- gedit(width = 20, label = "Unit", cont = ds.e.gfl) ds.e.rep <- gedit(width = 20, label = "Replicates", cont = ds.e.gfl) ds.e.obs <- gedit(width = 60, label = "Observed", cont = ds.e.gfl) ds.e.obu <- gedit(width = 20, label = "Unit", cont = ds.e.gfl) generate_grid.gb.line <- ggroup(cont = ds.editor) generate_grid.gb <- gbutton("Generate grid for entering kinetic data", cont = generate_grid.gb.line, width = 250, handler = empty_grid_handler) tooltip(generate_grid.gb) <- "Overwrites the kinetic data shown to the right" # Data upload area {{{3 tmptextfile <- "" # Initialize file name for imported data tmptextskip <- 0 # Initialize number of lines to be skipped tmptexttime <- "V1" # Initialize name of time variable if no header row upload_dataset.gf <- gfile(text = "Upload text file", cont = ds.editor, handler = load_text_file_with_data) # Import options {{{3 ds.e.import <- ggroup(cont = ds.editor, horizontal = FALSE) visible(ds.e.import) <- FALSE ds.e.preview <- ggroup(cont = ds.e.import, # width = 540, height = 150, ext.args = list(layout = list(type="vbox", align = "center"))) ds.e.up.text <- ghtml("", cont = ds.e.preview, width = 530, height = 150) ds.e.up.import.line <- ggroup(cont = ds.e.import) ds.e.up.import <- gbutton("Import using options specified below", cont = ds.e.up.import.line, width = 250, handler = new_ds_from_csv_handler) ds.e.up.options <- ggroup(cont = ds.e.import, width = 200, horizontal = FALSE) ds.e.up.skip <- gedit(tmptextskip, label = "Comment lines", width = 20, cont = ds.e.up.options) ds.e.up.header <- gcheckbox(cont = ds.e.up.options, label = "Column names", checked = TRUE) ds.e.up.sep <- gcombobox(c("whitespace", ";", ","), cont = ds.e.up.options, width = 50, selected = 1, label = "Separator") ds.e.up.dec <- gcombobox(c(".", ","), cont = ds.e.up.options, width = 50, selected = 1, label = "Decimal") ds.e.up.widelong <- gradio(c("wide", "long"), horizontal = TRUE, width = 100, label = "Format", cont = ds.e.up.options, handler = function(h, ...) { widelong = svalue(h$obj, index = TRUE) svalue(ds.e.up.wlstack) <- widelong }) ds.e.up.wlstack <- gstackwidget(cont = ds.e.import) ds.e.up.wide <- ggroup(cont = ds.e.up.wlstack, horizontal = FALSE, width = 300) ds.e.up.wide.time <- gedit(tmptexttime, cont = ds.e.up.wide, label = "Time column") ds.e.up.long <- ggroup(cont = ds.e.up.wlstack, horizontal = FALSE, width = 300) ds.e.up.long.name <- gedit("name", cont = ds.e.up.long, label = "Observed variables") ds.e.up.long.time <- gedit(tmptexttime, cont = ds.e.up.long, label = "Time column") ds.e.up.long.value <- gedit("value", cont = ds.e.up.long, label = "Value column") ds.e.up.long.err <- gedit("err", cont = ds.e.up.long, label = "Relative errors") svalue(ds.e.up.wlstack) <- 1 # center: Model editor {{{1 m.editor <- gframe("", horizontal = FALSE, cont = center, width = 600, label = "Model") # Handler functions {{{2 # For top row buttons {{{3 stage_model <- function(m.new) { m.cur <<- m.new update_m_editor() m.copy$call_Ext("disable") m.delete$call_Ext("disable") } new_model_handler <- function(h, ...) { m.new <- m.empty m.new$name <- "New model" stage_model(m.new) } copy_model_handler <- function(h, ...) { m.new <- m.cur m.new$name <- paste("Copy of ", m.cur$name) stage_model(m.new) } delete_model_handler <- function(h, ...) { m.i <- svalue(m.gtable, index = TRUE) ws$delete_m(m.i) update_m.df() p.modified <<- TRUE } keep_m_changes_handler <- function(h, ...) { spec <- list() for (obs.i in 1:length(m.e.rows)) { to_string <- svalue(m.e.to[[obs.i]]) if (length(to_string) == 0) to_vector = NULL else to_vector = strsplit(svalue(m.e.to[[obs.i]]), ", ")[[1]] spec[[obs.i]] <- mkinsub(svalue(m.e.type[[obs.i]]), to = to_vector, sink = svalue(m.e.sink[[obs.i]])) names(spec)[[obs.i]] <- svalue(m.e.obs[[obs.i]]) } m.cur <<- mkinmod(use_of_ff = svalue(m.ff.gc), speclist = spec) m.cur$name <<- svalue(m.name.ge) m.i <- svalue(m.gtable, index = TRUE) if (!is.null(m.i) && !is.na(m.i) && ws$m[[m.i]]$name == m.cur$name) { gconfirm(paste("Do you want to overwrite model", m.cur$name, "?"), parent = w, handler = function(h, ...) { ws$m[[m.i]] <- m.cur update_m.df() p.modified <<- TRUE svalue(p.observed) <- paste(ws$observed, collapse = ", ") }) } else { ws$add_m(list(m.cur)) update_m.df() p.modified <<- TRUE svalue(p.observed) <- paste(ws$observed, collapse = ", ") } } # Add and remove observed variables {{{3 add_observed <- function(obs.i) { if (obs.i == length(ws$observed)) { m.add_observed$call_Ext("disable") } m.e.rows[[obs.i]] <<- ggroup(cont = m.editor, horizontal = TRUE) m.e.obs[[obs.i]] <<- gcombobox(ws$observed, selected = obs.i, width = gcb_observed_width, cont = m.e.rows[[obs.i]]) obs.types <- if (obs.i == 1) c("SFO", "FOMC", "DFOP", "HS", "SFORB") else c("SFO", "SFORB") m.e.type[[obs.i]] <<- gcombobox(obs.types, width = gcb_type_width, selected = 1L, cont = m.e.rows[[obs.i]]) glabel("to", cont = m.e.rows[[obs.i]]) m.e.to[[obs.i]] <<- gcombobox(ws$observed, selected = 0L, width = gcb_to_width, editable = TRUE, ext.args = list(multiSelect = TRUE), cont = m.e.rows[[obs.i]]) m.e.sink[[obs.i]] <<- gcheckbox("Sink", width = gcb_sink_width, checked = TRUE, cont = m.e.rows[[obs.i]]) if (obs.i > 1) { gbutton("Remove observed variable", handler = remove_observed_handler, action = obs.i, cont = m.e.rows[[obs.i]]) } } add_observed_handler <- function(h, ...) { obs.i <- length(m.e.rows) + 1 add_observed(obs.i) } remove_observed_handler <- function(h, ...) { m.cur$spec[[h$action]] <<- NULL update_m_editor() } # Update the model editor {{{3 update_m_editor <- function() { svalue(m.name.ge) <- m.cur$name svalue(m.ff.gc) <- m.cur$use_of_ff for (oldrow.i in seq_along(m.e.rows)) { delete(m.editor, m.e.rows[[oldrow.i]]) } m.keep$call_Ext("enable") m.e.rows <<- m.e.obs <<- m.e.type <<- m.e.to <<- m.e.sink <<- list() if (length(m.cur$spec) == length(ws$observed)) { m.add_observed$call_Ext("disable") } else { m.add_observed$call_Ext("enable") } show_m_spec() } # Widget setup {{{2 # Line 1 with buttons {{{3 m.e.buttons <- ggroup(cont = m.editor, horizontal = TRUE) m.e.new <- gbutton("New model", cont = m.e.buttons, handler = new_model_handler) m.copy <- gbutton("Copy model", cont = m.e.buttons, handler = copy_model_handler, ext.args = list(disabled = TRUE)) m.delete <- gbutton("Delete model", cont = m.e.buttons, handler = delete_model_handler, ext.args = list(disabled = TRUE)) m.keep <- gbutton("Keep changes", cont = m.e.buttons, handler = keep_m_changes_handler) m.keep$call_Ext("disable") # Formlayout for meta data {{{3 m.e.gfl <- gformlayout(cont = m.editor) m.name.ge <- gedit(label = "Model name", width = 60, cont = m.e.gfl) m.ff.gc <- gcombobox(c("min", "max"), label = "Use of formation fractions", cont = m.e.gfl) svalue(m.ff.gc) <- m.cur$use_of_ff m.add_observed.line <- ggroup(cont = m.editor) m.add_observed <- gbutton("Add observed variable", width = 150, cont = m.add_observed.line, handler = add_observed_handler) m.add_observed$call_Ext("disable") # Model specification {{{3 m.e.rows <- m.e.obs <- m.e.type <- m.e.to <- m.e.sink <- list() # Show the model specification {{{4 show_m_spec <- function() { for (obs.i in seq_along(m.cur$spec)) { obs.name <- names(m.cur$spec)[[obs.i]] add_observed(obs.i) svalue(m.e.obs[[obs.i]]) <<- obs.name svalue(m.e.type[[obs.i]]) <<- m.cur$spec[[obs.i]]$type obs.to = m.cur$spec[[obs.i]]$to obs.to_string_R = paste(obs.to, collapse = ", ") obs.to_string_JS = paste0("['", paste(obs.to, collapse = "', '"), "']") # Set R and Ext values separately, as multiple selections are not supported svalue(m.e.to[[obs.i]]) <<- obs.to_string_R m.e.to[[obs.i]]$call_Ext("select", String(obs.to_string_JS)) svalue(m.e.sink[[obs.i]]) <<- m.cur$spec[[obs.i]]$sink } } show_m_spec() # center: Fit configuration {{{1 f.config <- gframe("", horizontal = FALSE, cont = center, label = "Configuration") # Handler functions {{{2 run_confirm_message <- paste("The progress of the fit is shown in the R console. ", if (interactive()) { paste("You can cancel", "the optimisation by switching to the window running R", "and pressing Ctrl-C (in terminals) or Escape (in", "the Windows R GUI). " ) } else "", "Proceed to start the fit?", sep = "") run_fit_handler <- function(h, ...) { #{{{3 gconfirm(run_confirm_message, handler = function(h, ...) { Parameters <- f.gg.parms[,] Parameters.de <- subset(Parameters, Type == "deparm") deparms <- Parameters.de$Initial names(deparms) <- Parameters.de$Name defixed <- names(deparms[Parameters.de$Fixed]) Parameters.ini <- subset(Parameters, Type == "state") iniparms <- Parameters.ini$Initial names(iniparms) <- sub("_0", "", Parameters.ini$Name) inifixed <- names(iniparms[Parameters.ini$Fixed]) if (svalue(f.gg.opts.plot)) { if (.Platform$OS.type == "windows") { # When on windows, check for an active windows device. If not present, # open one if (attr(dev.cur(), "names") != "windows") windows() } } ftmp <<- mkinfit(m.cur, override(ds.cur$data), state.ini = iniparms, fixed_initials = inifixed, parms.ini = deparms, fixed_parms = defixed, plot = svalue(f.gg.opts.plot), solution_type = svalue(f.gg.opts.st), atol = as.numeric(svalue(f.gg.opts.atol)), rtol = as.numeric(svalue(f.gg.opts.rtol)), transform_rates = svalue(f.gg.opts.transform_rates), transform_fractions = svalue(f.gg.opts.transform_fractions), reweight.tol = as.numeric(svalue(f.gg.opts.reweight.tol)), reweight.max.iter = as.numeric(svalue(f.gg.opts.reweight.max.iter)), error_model = svalue(f.gg.opts.error_model), error_model_algorithm = svalue(f.gg.opts.error_model_algorithm) ) ftmp$optimised <<- TRUE ftmp$ds <<- ds.cur ws$ftmp <<- ftmp ws$ftmp$Name <<- "Temporary (fitted)" ftmp$name <<- paste(m.cur$name, "-", ds.cur$title) update_f.df() stmp <<- summary(ftmp) f.gg.parms[,] <- get_Parameters(stmp, TRUE) show_plot("Optimised") f.keep$call_Ext("enable") show.initial.gb.o$call_Ext("enable") svalue(f.gg.opts.st) <- ftmp$solution_type svalue(f.running.label) <- "Terminated" update_f_results() }) svalue(f.running.label) <- "Running..." } delete_fit_handler <- function(h, ...) { # {{{3 f.i <- svalue(f.gtable, index = TRUE) if (f.i == 1) { gmessage("Will not delete temporary fit") } else { ws$delete_f(f.i - 1) update_f.df() p.modified <<- TRUE } } keep_fit_handler <- function(h, ...) { # {{{3 ftmp$name <<- svalue(r.name) ws$add_f(list(ftmp)) ws$ftmp <<- list(Name = "") update_f.df() update_plot_obssel() p.modified <<- TRUE } export_csv_handler <- function(h, ...) { # {{{3 csv_file <- paste(ftmp$ds$title, "_", ftmp$mkinmod$name, ".csv", sep = "") solution_type = ftmp$solution_type parms.all <- c(ftmp$bparms.optim, ftmp$bparms.fixed) ininames <- c( rownames(subset(ftmp$start, type == "state")), rownames(subset(ftmp$fixed, type == "state"))) odeini <- parms.all[ininames] # Order initial state variables names(odeini) <- sub("_0", "", names(odeini)) odeini <- odeini[names(ftmp$mkinmod$diffs)] xlim = range(ftmp$data$time) outtimes <- seq(xlim[1], xlim[2], length.out=200) odenames <- c( rownames(subset(ftmp$start, type == "deparm")), rownames(subset(ftmp$fixed, type == "deparm"))) odeparms <- parms.all[odenames] out <- mkinpredict(ftmp$mkinmod, odeparms, odeini, outtimes, solution_type = solution_type, atol = ftmp$atol, rtol = ftmp$rtol) write.csv(out, csv_file) svalue(sb) <- paste("Wrote model predictions to", file.path(getwd(), csv_file)) } get_Parameters <- function(stmp, optimised) # {{{3 { pars <- rbind(stmp$start[1:2], stmp$fixed) pars$fixed <- c(rep(FALSE, length(stmp$start$value)), rep(TRUE, length(stmp$fixed$value))) pars$name <- rownames(pars) Parameters <- data.frame(Name = pars$name, Type = pars$type, Initial = pars$value, Fixed = pars$fixed, Optimised = as.numeric(NA)) Parameters <- rbind(subset(Parameters, Type == "state"), subset(Parameters, Type == "deparm"), subset(Parameters, Type == "error")) rownames(Parameters) <- Parameters$Name if (optimised) { Parameters[rownames(stmp$bpar), "Optimised"] <- stmp$bpar[, "Estimate"] } return(Parameters) } show_plot <- function(type) { Parameters <- f.gg.parms[,] Parameters.de <- subset(Parameters, Type == "deparm", type) stateparms <- subset(Parameters, Type == "state")[[type]] deparms <- as.numeric(Parameters.de[[type]]) names(deparms) <- rownames(Parameters.de) if (type == "Initial") { ftmp <<- suppressWarnings(mkinfit(m.cur, override(ds.cur$data), parms.ini = deparms, state.ini = stateparms, fixed_parms = names(deparms), fixed_initials = names(stateparms), err = "err", quiet = TRUE, method.modFit = "Marq", control.modFit = list(maxiter = 0))) ftmp$ds <<- ds.cur } svalue(plot.ftmp.gi) <<- plot_ftmp_png() svalue(plot.ftmp.savefile) <- paste0(ftmp$mkinmod$name, " - ", ftmp$ds$title, ".", plot_format) svalue(plot.confint.gi) <<- if (type == "Initial") NA else plot_confint_png() svalue(right) <- 4 } # Widget setup {{{2 # Line 1 with buttons {{{3 f.run.line <- ggroup(cont = f.config) f.run <- gbutton("Run fit", width = 100, cont = f.run.line, handler = run_fit_handler, ext.args = list(disabled = TRUE)) f.running.line <- ggroup(cont = f.config) f.running_noconf <- paste("No fit configured. Please select a dataset and a model and", "press the button 'Configure fit' on the left.") f.running.label <- glabel(f.running_noconf, cont = f.running.line) # Fit options forms {{{3 f.gg.opts.g <- ggroup(cont = f.config) # First group {{{4 f.gg.opts.1 <- gformlayout(cont = f.gg.opts.g) solution_types <- c("auto", "analytical", "eigen", "deSolve") f.gg.opts.plot <- gcheckbox("Plot during the fit", cont = f.gg.opts.1, checked = FALSE) f.gg.opts.st <- gcombobox(solution_types, selected = 1, label = "solution_type", width = 160, cont = f.gg.opts.1) f.gg.opts.atol <- gedit(1e-8, label = "atol", width = 20, cont = f.gg.opts.1) f.gg.opts.rtol <- gedit(1e-10, label = "rtol", width = 20, cont = f.gg.opts.1) error_models <- c("const", "obs", "tc") f.gg.opts.error_model <- gcombobox(error_models, selected = 1, label = "error_model", width = 160, cont = f.gg.opts.1) error_model_algorithms <- c("d_3", "direct", "threestep", "IRLS", "OLS") f.gg.opts.error_model_algorithm <- gcombobox(error_model_algorithms, selected = 5, label = "error_model_algorithm", width = 160, cont = f.gg.opts.1) f.gg.opts.maxit <- gedit(200, label = "maxit", width = 20, cont = f.gg.opts.1) # Second group {{{4 f.gg.opts.2 <- gformlayout(cont = f.gg.opts.g) f.gg.opts.transform_rates <- gcheckbox("transform_rates", cont = f.gg.opts.2, checked = TRUE) f.gg.opts.transform_fractions <- gcheckbox("transform_fractions", cont = f.gg.opts.2, checked = TRUE) weights <- c("manual", "none", "std", "mean") f.gg.opts.reweight.tol <- gedit(1e-8, label = "reweight.tol", width = 20, cont = f.gg.opts.2) f.gg.opts.reweight.max.iter <- gedit(10, label = "reweight.max.iter", width = 20, cont = f.gg.opts.2) f.gg.plotopts <- ggroup(cont = f.gg.opts.g, horizontal = FALSE, width = 80) f.gg.po.format <- gcombobox(plot_formats, selected = 1, cont = f.gg.plotopts, width = 50, handler = function(h, ...) { plot_format <<- svalue(h$obj) svalue(plot.ftmp.savefile) <<- gsub("...$", plot_format, svalue(plot.ftmp.savefile)) }) plot_format <- svalue(f.gg.po.format) f.gg.po.legend <- gcheckbox("legend", cont = f.gg.plotopts, checked = TRUE) f.gg.po.obssel <- gcheckboxgroup("", cont = f.gg.plotopts, checked = TRUE) visible(f.gg.po.obssel) <- FALSE # Parameter table {{{3 f.parameters.line <- ggroup(cont = f.config, horizontal = TRUE) get_initials_handler <- function(h, ...) { f.i <- svalue(get.initials.gc, index = TRUE) fit <- if (f.i == 1) ftmp else ws$f[[f.i - 1]] got_initials <- c(fit$bparms.fixed, fit$bparms.optim) parnames <- f.gg.parms[,"Name"] newparnames <- names(got_initials) commonparnames <- intersect(parnames, newparnames) f.gg.parms[commonparnames, "Initial"] <- got_initials[commonparnames] } get.initials.gb <- gbutton("Get starting parameters from", cont = f.parameters.line, handler = get_initials_handler) get.initials.gc <- gcombobox(paste("Result", f.df$Name), width = 200, cont = f.parameters.line) show.initial.gb.u <- gbutton("Plot unoptimised", handler = function(h, ...) show_plot("Initial"), cont = f.parameters.line) tooltip(show.initial.gb.u) <- "Show model with inital parameters shown below" show.initial.gb.o <- gbutton("Plot optimised", ext.args = list(disabled = TRUE), handler = function(h, ...) show_plot("Optimised"), cont = f.parameters.line) tooltip(show.initial.gb.o) <- "Show model with optimised parameters shown below" # Empty parameter table Parameters <- Parameters.empty <- data.frame( Name = "", Type = factor("state", levels = c("state", "deparm")), Initial = numeric(1), Fixed = logical(1), Optimised = numeric(1)) # Dataframe with initial and optimised parameters {{{4 f.gg.parms <- gdf(Parameters, cont = f.config, height = 500, name = "Starting parameters", do_add_remove_buttons = FALSE) size(f.gg.parms) <- list(columnWidths = c(220, 50, 65, 50, 65)) # Do not show fit option widgets when no fit is configured show_fit_option_widgets <- function(show) { visible(f.gg.opts.g) <- show visible(f.parameters.line) <- show visible(f.gg.parms) <- show } show_fit_option_widgets(FALSE) # center: Results viewer {{{1 r.viewer <- gframe("", horizontal = FALSE, cont = center, label = "Result") # Row with buttons {{{2 r.buttons <- ggroup(cont = r.viewer, horizontal = TRUE) f.delete <- gbutton("Delete fit", cont = r.buttons, handler = delete_fit_handler, ext.args = list(disabled = TRUE)) f.keep <- gbutton("Keep fit", cont = r.buttons, handler = keep_fit_handler) tooltip(f.keep) <- "Store the optimised model with all settings and the current dataset in the fit list" f.keep$call_Ext("disable") f.csv <- gbutton("Export csv", cont = r.buttons, handler = export_csv_handler) tooltip(f.csv) <- "Save model predictions in a text file as comma separated values for plotting" # Result name {{{2 r.line.name <- ggroup(cont = r.viewer, horizontal = TRUE) r.name <- gedit("", label = "Result name", width = 50, cont = r.line.name) # Optimised parameter table {{{2 par.df.empty <- data.frame( Parameter = character(1), Estimate = numeric(1), "Pr(>t)" = numeric(1), Lower = numeric(1), Upper = numeric(1), check.names = FALSE) r.par.gf <- gframe("Optimised parameters", cont = r.viewer, horizontal = FALSE, spacing = 0) r.parameters <- gtable(par.df.empty, cont = r.par.gf, height = 200, ext.args = list(resizable = TRUE, resizeHandles = 's')) # Tables with chi2, ff, DT50 {{{2 r.frames <- ggroup(cont = r.viewer, horizontal = TRUE, spacing = 0) r.frames.chi2 <- gframe("Chi2 errors [%]", cont = r.frames, horizontal = TRUE, spacing = 0) chi2.df.empty = data.frame(Variable = character(1), Error = character(1), n.opt = character(1), df = character(1), stringsAsFactors = FALSE) r.frames.chi2.gt <- gtable(chi2.df.empty, cont = r.frames.chi2, width = 180, height = 150) size(r.frames.chi2.gt) <- list(columnWidths = c(60, 35, 35, 15)) r.frames.ff <- gframe("Formation fractions", cont = r.frames, horizontal = TRUE, spacing = 0) ff.df.empty = data.frame(Path = character(1), ff = character(1), stringsAsFactors = FALSE) r.frames.ff.gt <- gtable(ff.df.empty, cont = r.frames.ff, width = 150, height = 150) size(r.frames.ff.gt) <- list(columnWidths = c(80, 15)) r.frames.distimes <- gframe("Disappearance times", cont = r.frames, horizontal = TRUE, spacing = 0) distimes.df.empty = data.frame(Variable = character(1), DT50 = character(1), stringsAsFactors = FALSE) r.frames.distimes.gt <- gtable(distimes.df.empty, cont = r.frames.distimes, width = 150, height = 150) # Summary {{{2 f.gg.summary <- gframe("Summary", height = 400, use.scrollwindow = TRUE, cont = r.viewer, horizontal = FALSE) f.gg.summary.topline <- ggroup(cont = f.gg.summary, horizontal = TRUE) f.gg.summary.filename <- gedit("", width = 40, cont = f.gg.summary.topline) f.gg.summary.savebutton <- gbutton("Save summary", cont = f.gg.summary.topline, handler = function(h, ...) { filename <- svalue(f.gg.summary.filename) if (file.exists(filename)) { gconfirm(paste("File", filename, "exists. Overwrite?"), parent = w, handler = function(h, ...) { capture.output(stmp, file = filename) }) } else { capture.output(summary(ftmp), file = filename) } }) f.gg.summary.listing <- ghtml("", cont = f.gg.summary) svalue(center) <- 1 # right: Viewing area {{{1 # Workflow {{{2 workflow.gg <- ggroup(cont = right, label = "Workflow", width = 480, height = 570, ext.args = list(layout = list(type="vbox", align = "center"))) workflow_url <- "/custom/gmkin_png/workflow/gmkin_workflow_434x569.png" workflow.gi <- gimage(workflow_url, size = c(434, 569), label = "Workflow", cont = workflow.gg) # Data editor {{{2 ds.e.gdf <- gdf(ds.cur$data, label = "Data", name = "Kinetic data", do_add_remove_buttons = FALSE, width = 488, height = 577, cont = right) # Model Gallery {{{2 m.g.gg <- ggroup(cont = right, label = "Model gallery", ext.args = list(layout = list(type="vbox", align = "center"))) m.g.rows <- list() m.g.buttonrows <- list() m.g.fields <- list() m.g.buttons <- list() add_gallery_model_handler <- function(h, ...) { i_j <- h$action ws$add_m(UBA_model_gallery[[i_j[1]]][i_j[2]]) update_m.df() m.i <- nrow(m.df) svalue(c.m) <- m.df[m.i, "Name"] m.cur <<- ws$m[[m.i]] update_m_editor() m.delete$call_Ext("enable") m.copy$call_Ext("enable") if (!is.null(svalue(ds.gtable, index = TRUE))) { if (length(svalue(ds.gtable)) > 0) { if (!is.na(svalue(ds.gtable))) f.conf$call_Ext("enable") } } svalue(center) <- 3 } model_gallery_created <- FALSE m.g.loading <- glabel("Loading the model gallery, please wait...