# gWidgetsWWW2 GUI for mkin {{{1
# Copyright (C) 2013,2014,2015 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
", 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))) } 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() } 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) 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 <- gbutton("Generate grid for entering kinetic data", cont = ds.editor, 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 = 480, height = 150, ext.args = list(layout = list(type="vbox", align = "center"))) ds.e.up.text <- ghtml("", cont = ds.e.preview, width = 400, height = 150) ds.e.up.import <- gbutton("Import using options specified below", cont = ds.e.import, 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 = 100, 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, 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") } add_model <- function(m.new) { ws$add_m(list(m.new)) update_m.df() p.modified <<- TRUE } 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$title) 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) add_model(m.cur) 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 = 0L, 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, 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 <- gbutton("Add observed variable", cont = m.editor, 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)) } } show_m_spec() # center: Fit configuration {{{1 f.config <- gframe("", horizontal = FALSE, cont = center, label = "Configuration") # Handler functions {{{2 run_fit <- function() { #{{{3 # 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]) # weight <- svalue(f.gg.opts.weight) # if (weight == "manual") { # err = "err" # } else { # err = NULL # } # reweight.method <- svalue(f.gg.opts.reweight.method) # if (reweight.method == "none") reweight.method = NULL # ftmp <<- mkinfit(ftmp$mkinmod, override(ds[[ds.i]]$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), # weight = weight, # err = err, # reweight.method = reweight.method, # reweight.tol = as.numeric(svalue(f.gg.opts.reweight.tol)), # reweight.max.iter = as.numeric(svalue(f.gg.opts.reweight.max.iter)), # method.modFit = svalue(f.gg.opts.method.modFit), # maxit.modFit = svalue(f.gg.opts.maxit.modFit) # ) # ftmp$ds.index <<- ds.i # ftmp$ds <<- ds[[ds.i]] # stmp <<- summary(ftmp) # show_plot("Optimised") # svalue(f.gg.opts.st) <- ftmp$solution_type # svalue(f.gg.opts.weight) <- ftmp$weight.ini # f.gg.parms[,] <- get_Parameters(stmp, TRUE) # svalue(f.gg.summary.filename) <<- paste(ftmp$ds$title, "_", ftmp$mkinmod$name, ".txt", sep = "") # svalue(f.gg.summary.listing) <<- c("
", capture.output(stmp), "") } delete_fit_handler <- function(h, ...) { # {{{3 f.i <- svalue(f.gtable, index = TRUE) ws$delete_f(f.i) update_f.df() p.modified <<- TRUE } keep_fit_handler <- function(h, ...) { # {{{3 # f.cur <<- as.character(length(f) + 1) # f[[f.cur]] <<- ftmp # s[[f.cur]] <<- stmp # update_f.df() # f.gtable[,] <<- f.df # delete(f.gg.plotopts, f.gg.po.obssel) # f.gg.po.obssel <<- gcheckboxgroup(names(ftmp$mkinmod$spec), # cont = f.gg.plotopts, # checked = TRUE) # delete(f.gg.buttons, get.initials.gc) # get.initials.gc <<- gcombobox(paste("Fit", f.df$Fit), # cont = f.gg.buttons) } 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")) # rownames(Parameters) <- Parameters$Name # if (optimised) { # Parameters[rownames(stmp$bpar), "Optimised"] <- stmp$bpar[, "Estimate"] # } # return(Parameters) } show_plot <- function(type, default = FALSE) { # 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" & default == FALSE) { # ftmp <<- suppressWarnings(mkinfit(ftmp$mkinmod, # override(ds[[ds.i]]$data), # parms.ini = deparms, # state.ini = stateparms, # fixed_parms = names(deparms), # fixed_initials = names(stateparms), # err = "err", # method.modFit = "Marq", # control.modFit = list(maxiter = 0))) # ftmp$ds.index <<- ds.i # ftmp$ds <<- ds[[ds.i]] # } # svalue(plot.ftmp.gi) <<- plot_ftmp_png() # svalue(plot.confint.gi) <<- plot_confint_png() } # Widget setup {{{2 # Line 1 with buttons {{{3 f.buttons <- ggroup(cont = f.config, horizontal = TRUE) f.run <- gbutton("Run fit", cont = f.buttons, handler = function(h, ...) run_fit(), ext.args = list(disabled = TRUE)) f.delete <- gbutton("Delete fit", cont = f.buttons, handler = delete_fit_handler, ext.args = list(disabled = TRUE)) f.keep <- gbutton("Keep fit", cont = f.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") # center: Results viewer {{{1 r.viewer <- gframe("", horizontal = FALSE, cont = center, label = "Result") 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.png <- get_tempfile(ext = ".png") file.copy(system.file("GUI/gmkin_workflow_434x569.png", package = "gmkin"), workflow.png) workflow.gi <- gimage(workflow.png, size = c(434, 569), label = "Workflow", cont = workflow.gg) # # Kinetic Data {{{3 ds.e.gdf <- gdf(ds.cur$data, label = "Data editor", name = "Kinetic data", width = 488, height = 600, cont = right) workflow.png <- get_tempfile(ext = ".png") file.copy(system.file("GUI/gmkin_workflow_434x569.png", package = "gmkin"), workflow.png) workflow.gi <- gimage(workflow.png, size = c(434, 569), label = "Workflow", cont = workflow.gg) # Model Gallery {{{3 m.g.gg <- ggroup(cont = right, label = "Model gallery", width = 480, height = 570, ext.args = list(layout = list(type="vbox", align = "center"))) # Manual {{{2 gmkin_manual <- readLines(system.file("GUI/gmkin_manual.html", package = "gmkin")) gmb_start <- grep("", gmkin_manual) gmb_end <- grep("", gmkin_manual) gmkin_manual_body <- gmkin_manual[gmb_start:gmb_end] manual.gh <- ghtml(label = "Manual", paste0("