From c737c606058cb4c2a0805e2bec8ce356d01a627a Mon Sep 17 00:00:00 2001 From: Johannes Ranke Date: Thu, 22 Oct 2015 17:30:09 +0200 Subject: A lot of working components of the new layout --- .Rbuildignore | 4 +- .gitignore | 4 + DESCRIPTION | 7 +- GNUmakefile | 12 +- NAMESPACE | 4 +- NEWS.md | 4 +- R/gmkinws.R | 129 ++++ data/FOCUS_2006.RData | Bin 0 -> 8362 bytes data/FOCUS_2006_Z.RData | Bin 0 -> 71960 bytes data/FOCUS_2006_Z_gmkin.RData | Bin 69426 -> 0 bytes data/FOCUS_2006_gmkin.RData | Bin 5711 -> 0 bytes inst/GUI/gmkin.R | 1370 +++++++++------------------------- inst/GUI/gmkin_manual.html | 233 ++++++ inst/GUI/gmkin_workflow_434x569.png | Bin 0 -> 43317 bytes inst/GUI/gmkin_workflow_inkscape.svg | 556 ++++++++++++++ man/FOCUS_2006.Rd | 31 + man/FOCUS_2006_Z.Rd | 28 + man/FOCUS_2006_Z_gmkin.Rd | 28 - man/FOCUS_2006_gmkin.Rd | 30 - vignettes/gmkin_manual.Rmd | 2 +- vignettes/gmkin_manual.html | 2 +- vignettes/gmkin_manual.md | 408 ++++++++++ 22 files changed, 1756 insertions(+), 1096 deletions(-) create mode 100644 R/gmkinws.R create mode 100644 data/FOCUS_2006.RData create mode 100644 data/FOCUS_2006_Z.RData delete mode 100644 data/FOCUS_2006_Z_gmkin.RData delete mode 100644 data/FOCUS_2006_gmkin.RData create mode 100644 inst/GUI/gmkin_manual.html create mode 100644 inst/GUI/gmkin_workflow_434x569.png create mode 100644 inst/GUI/gmkin_workflow_inkscape.svg create mode 100644 man/FOCUS_2006.Rd create mode 100644 man/FOCUS_2006_Z.Rd delete mode 100644 man/FOCUS_2006_Z_gmkin.Rd delete mode 100644 man/FOCUS_2006_gmkin.Rd create mode 100644 vignettes/gmkin_manual.md diff --git a/.Rbuildignore b/.Rbuildignore index 10252a8..d52bde1 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -1,8 +1,10 @@ GNUmakefile -NEWS.md README.html gmkin_screenshot.png Rprofile vignettes/.build.timestamp vignettes/cache vignettes/gmkin_manual_cache +vignettes/gmkin_manual.R +vignettes/gmkin_manual.md +inst/GUI/gmkin_workflow_inkscape.svg diff --git a/.gitignore b/.gitignore index d2ac9ac..e3c1891 100644 --- a/.gitignore +++ b/.gitignore @@ -1,4 +1,8 @@ NEWS +cache/* +gmkin.Rcheck/* inst/web* +inst/GUI/old.R vignettes/cache vignettes/gmkin_manual_cache +*.swp diff --git a/DESCRIPTION b/DESCRIPTION index 1496ce1..853236a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,15 +1,16 @@ Package: gmkin Type: Package Title: Graphical User Interface for Fitting Kinetic Models to Chemical Degradation Data -Version: 0.5-10.9000 -Date: 2015-08-26 +Version: 0.6-00.9000 +Date: 2015-10-19 Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"), email = "jranke@uni-bremen.de"), person("Eurofins Regulatory AG", role = "cph")) Description: Browser based graphical user interface for R package mkin, based on the gWidgetsWWW2 package. Both gmkin and gWidgetsWWW2 are developed on GitHub, but are also available from the R-Forge repository. -Depends: mkin (>= 0.9-32), gWidgetsWWW2 +Depends: mkin (> 0.9-40), gWidgetsWWW2 (>= 0.4-6) +Imports: R6, markdown Suggests: knitr, rmarkdown License: GPL LazyLoad: yes diff --git a/GNUmakefile b/GNUmakefile index af98dbe..0a919b8 100644 --- a/GNUmakefile +++ b/GNUmakefile @@ -18,7 +18,7 @@ SDDIR ?= $(RFSVN)/www/gmkin_static pkgfiles = NEWS.md \ data/* \ DESCRIPTION \ - inst/GUI/gmkin.R \ + inst/GUI/* \ man/* \ NAMESPACE \ R/* \ @@ -63,6 +63,16 @@ README.html: README.md vignettes/gmkin_manual.html: vignettes/gmkin_manual.Rmd "$(RBIN)/Rscript" -e "tools::buildVignette(file = 'vignettes/gmkin_manual.Rmd', dir = 'vignettes')" +vignettes/gmkin_manual.md: vignettes/gmkin_manual.Rmd + cd vignettes; \ + "$(RBIN)/Rscript" -e "knitr::knit('gmkin_manual.Rmd', out = 'gmkin_manual.md')"; \ + +inst/GUI/gmkin_manual.html: vignettes/gmkin_manual.md + cd vignettes; \ + pandoc -o ../inst/GUI/gmkin_manual.html gmkin_manual.md --toc --self-contained + +manual: vignettes/gmkin_manual.html inst/GUI/gmkin_manual.html + vignettes: vignettes/gmkin_manual.html sd: diff --git a/NAMESPACE b/NAMESPACE index 4ddb2b5..ca61543 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,5 +1,5 @@ # Export all names -exportPattern(".") +export("gmkin") # Import all packages listed as Imports or Depends -import(mkin, gWidgetsWWW2) +import(mkin, gWidgetsWWW2, R6, markdown) diff --git a/NEWS.md b/NEWS.md index c7410bc..4aed96d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,8 +1,8 @@ # NEWS for package 'gmkin' -## gmkin 0.5-10.9000 - +## gmkin 0.6-0.9000 +- Completely rewritten user interface with a three column layout ## gmkin 0.5-10 (2015-05-08) diff --git a/R/gmkinws.R b/R/gmkinws.R new file mode 100644 index 0000000..c6f1ec5 --- /dev/null +++ b/R/gmkinws.R @@ -0,0 +1,129 @@ +# Copyright (C) 2015 Johannes Ranke +# Contact: jranke@uni-bremen.de + +# This file is part of the R package gmkin + +# mkin 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 + +#' A workspace class for gmkin +#' +#' @docType class +#' @importFrom R6 R6Class +#' @importFrom mkin mkinws +#' @export +#' @format An \code{\link{R6Class}} generator object. +#' @field observed Names of the observed variables in the datasets, named +#' by the names used in the models contained in field m +#' @field ds A list of datasets compatible with mkinfit (long format) +#' @field ds.cur Index of the currently selected dataset +#' @field m A list of mkinmod models +#' @field m.cur Index of the currently selected model +#' @field f A list of mkinfit objects +#' @field f.cur Index of the currently selected fit +#' @field s The summaries of the mkinfit objects in field f + +gmkinws <- R6Class("gmkinws", + public = list( + observed = NULL, + ds = list(), + ds.cur = NULL, + m = list(), + m.cur = NULL, + f = list(), + f.cur = NULL, + s = NA, + + initialize = function(ds, m, f, ds.cur = NA, m.cur = NA, f.cur = NA) { + + ## Datasets + if (!missing(ds)) { + self$check_ds(ds) + self$ds = ds + self$ds.cur = ds.cur + + # Collect names of observed variables + self$observed <- unique(sapply(ds, function(x) x$observed)) + } + + ## Models + if (!missing(m)) { + self$check_m(m) + self$m <- m + } + self$m.cur = m.cur + + ## Fits + if (!missing(f)) { + self$f <- f + } + self$f.cur = f.cur + + invisible(self) + }, + + check_ds = function(ds) { + errmsg <- "ds must be a list of mkinds objects" + if (!is.list(ds)) stop(errmsg) + lapply(ds, function(x) { + if (!is(x, "mkinds")) + stop(errmsg) + } + ) + }, + + add_ds = function(ds) { + self$check_ds(ds) + common_names = intersect(names(self$ds), names(ds)) + if (length(common_names) > 0) stop("Dataset name(s) ", paste(common_names, collapse = ", "), " already used.") + else append(self$ds, ds) + + # Update names of observed variables + observed <- unique(sapply(ds, function(x) x$observed)) + self$observed <- union(self$observed, observed) + + invisible(self) + }, + + check_m = function(m) { + errmsg <- "m must be a list of mkinmod objects" + if (!is.list(m)) stop(errmsg) + lapply(m, function(x) { + if (!is(x, "mkinmod")) + stop(errmsg) + } + ) + }, + + add_m = function(m) { + self$check_m(m) + common_names = intersect(names(self$m), names(m)) + if (length(common_names) > 0) stop("Model name(s) ", paste(common_names, collapse = ", "), " already used.") + else self$m = c(self$m, m) + invisible(self) + } + ) +) + +#' @export +print.gmkinws <- function(x, ...) { + cat(" workspace object\n") + cat("\nDatasets:\n") + print(x$ds) + cat("\nModels:\n") + print(x$m) + cat("Current selections:\n") + cat("Dataset ", x$ds.cur, ", Model ", x$m.cur, ", Fit ", x$f.cur, "\n", sep = "") + cat("\nFits:\n") + print(names(x$f)) +} diff --git a/data/FOCUS_2006.RData b/data/FOCUS_2006.RData new file mode 100644 index 0000000..4587396 Binary files /dev/null and b/data/FOCUS_2006.RData differ diff --git a/data/FOCUS_2006_Z.RData b/data/FOCUS_2006_Z.RData new file mode 100644 index 0000000..a65884b Binary files /dev/null and b/data/FOCUS_2006_Z.RData differ diff --git a/data/FOCUS_2006_Z_gmkin.RData b/data/FOCUS_2006_Z_gmkin.RData deleted file mode 100644 index 0ff92d1..0000000 Binary files a/data/FOCUS_2006_Z_gmkin.RData and /dev/null differ diff --git a/data/FOCUS_2006_gmkin.RData b/data/FOCUS_2006_gmkin.RData deleted file mode 100644 index 0440b07..0000000 Binary files a/data/FOCUS_2006_gmkin.RData and /dev/null differ diff --git a/inst/GUI/gmkin.R b/inst/GUI/gmkin.R index 7fef7a1..0b615c4 100644 --- a/inst/GUI/gmkin.R +++ b/inst/GUI/gmkin.R @@ -1,12 +1,12 @@ # gWidgetsWWW2 GUI for mkin {{{1 -# Copyright (C) 2013,2014 Johannes Ranke +# 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 mkin +# This file is part of the R package gmkin -# mkin is free software: you can redistribute it and/or modify it under the +# 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. @@ -20,1061 +20,377 @@ # this program. If not, see # Set the GUI title and create the basic widget layout {{{1 -w <- gwindow("gmkin - Browser based GUI for kinetic evaluations using mkin") -sb <- gstatusbar(paste("Powered by gWidgetsWWW2 (ExtJS, Rook)", - "and mkin (FME, deSolve and minpack.lm)", - "--- Working directory is", getwd()), cont = w) -pg <- gpanedgroup(cont = w, default.size = 260) -center <- gnotebook(cont = pg) -left <- gvbox(cont = pg, use.scrollwindow = TRUE) -# Set initial values {{{1 -# Initial project workspace contents {{{2 -project_name <- "FOCUS_2006_gmkin" -project_file <- paste0(project_name, ".RData") -workspace <- get(project_name) # From dataset distributed with mkin -studies.df <- workspace$studies.df # dataframe containing study titles -ds <- workspace$ds # list of datasets -ds.cur <- workspace$ds.cur # current dataset index -m <- workspace$m # list with mkinmod models, amended with mkinmod$name -m.cur <- workspace$m.cur # m.cur current model index -f <- workspace$f # f list of fitted mkinfit objects -f.cur <- workspace$f.cur # current fit index -s <- workspace$s # list of summaries of the fitted mkinfit objects -# Initialise meta data objects so assignments within functions using <<- will {{{2 -# update them in the right environment -observed.all <- vector() # vector of names of observed variables in datasets -ds.df <- data.frame() -m.df <- data.frame() -f.df <- data.frame() -# Empty versions of meta data {{{2 -f.df.empty <- data.frame(Fit = as.integer(0), - Dataset = "", - Model = "", - stringsAsFactors = FALSE) +# Configuration {{{2 +left_width = 250 +right_width = 500 +save_keybinding = "Ctrl-X" +# Widgets {{{2 +window_title <- paste0("gmkin ", packageVersion("gmkin"), + "- Browser based GUI for kinetic evaluations using mkin") +w <- gwindow(window_title) +sb <- gstatusbar(paste("Powered by gWidgetsWWW2 (ExtJS, Rook)", + "and mkin (FME, deSolve and minpack.lm)", + "--- Working directory is", getwd()), cont = w) + +bl <- gborderlayout(cont = w, + #title = list(center = "Work", east = "Results"), + panels = c("center", "west", "east"), + collapsible = list(west = FALSE)) + +bl$set_panel_size("west", left_width) +bl$set_panel_size("east", right_width) + +center <- gnotebook(cont = bl, where = "center") +left <- gvbox(cont = bl, use.scrollwindow = TRUE, where = "west") +right <- gnotebook(cont = bl, use.scrollwindow = TRUE, where = "east") + # Helper functions {{{1 # Override function for making it possible to override original data points using the GUI {{{2 override <- function(d) { - data.frame(name = d$name, time = d$time, - value = ifelse(is.na(d$override), d$value, d$override), - err = d$err) + if (!is.null(d$override)) { + d_new <- data.frame(name = d$name, time = d$time, + value = ifelse(is.na(d$override), d$value, d$override), + err = d$err) + return(d_new) + } else { + return(d) + } +} +# Update dataframe with projects {{{2 +update_p.df <- function() { + wd_projects <- gsub(".gmkinws", "", dir(pattern = ".gmkinws$")) + if (length(wd_projects) > 0) { + p.df.wd <- data.frame(Name = wd_projects, + Source = rep("working directory", + length(wd_projects)), + stringsAsFactors = FALSE) + p.df <<- rbind(p.df.package, p.df.wd) + } else { + p.df <<- p.df.package + } } # Update dataframe with datasets {{{2 update_ds.df <- function() { - ds.n <- length(ds) - ds.df <<- data.frame(Index = 1:ds.n, - Title = character(ds.n), - Study = character(ds.n), - stringsAsFactors = FALSE) - for (i in 1:ds.n) - { - ds.index <- names(ds)[[i]] - ds.df[i, "Title"] <<- ds[[ds.index]]$title - ds.df[i, "Study"] <<- ds[[ds.index]]$study_nr - observed = as.character(unique(ds[[ds.index]]$data$name)) - observed.all <<- union(observed, observed.all) - } + ds.df <<- data.frame(Title = sapply(ws$ds, function(x) x$title)) } # Update dataframe with models {{{2 update_m.df <- function() { - m.n <- length(m) - m.df <<- data.frame(Index = 1:m.n, - Name = character(m.n), - stringsAsFactors = FALSE) - for (i in 1:m.n) { - m.index <- names(m)[[i]] - m.df[i, "Name"] <<- m[[m.index]]$name - } + m.df <<- data.frame(Name = names(ws$m)) } # Update dataframe with fits {{{2 update_f.df <- function() { - f.df <<- f.df.empty - f.count <- 0 - for (fit.index in names(f)) { - f.count <- f.count + 1 - ftmp <- f[[fit.index]] - f.df[f.count, "Fit"] <<- as.integer(f.count) - f.df[f.count, c("Dataset", "Model")] <<- c(ftmp$ds.index, ftmp$mkinmod$name) - } -} -# Initialise meta data objects {{{1 -update_ds.df() -update_m.df() -update_f.df() -# Widgets and handlers for project data {{{1 -prg <- gexpandgroup("Project file management", cont = left, horizontal = FALSE) -# Project data management handler functions {{{2 -upload_file_handler <- function(h, ...) -{ - # General - tmpfile <- normalizePath(svalue(h$obj), winslash = "/") - project_file <<- pr.gf$filename - project_name <<- try(load(tmpfile)) - if (inherits(project_name, "try-error")) { - galert(paste("Failed to load", project_file), parent = w) - } - - workspace <- get(project_name) - - # Check for old workspaces created using mkin < 0.9-32 that aren't loaded properly - workspace_old <- FALSE - if (length(workspace$f) > 0) { - if (is.null(workspace$f[[1]]$method.modFit)) { - stopmessage <- paste("Could not load workspace ", - project_file, - ". It seems it was created using mkin with version < 0.9-32", - sep = "") - galert(stopmessage, parent = w) - svalue(sb) <- stopmessage - workspace_old <- TRUE - } + f.df <- f.df.empty + if (!is.na(ftmp[1])) { + f.df[1, "Name"] <- c("Temporary (not fitted)") } - - if (!workspace_old) { - # Update project file name and status bar - svalue(pr.ge) <- project_name - svalue(sb) <- paste("Loaded project file", project_file) - - # Studies - studies.gdf[,] <- studies.df <- workspace$studies.df - - # Datasets - ds.cur <<- workspace$ds.cur - ds <<- workspace$ds - update_ds.df() - ds.gtable[,] <- ds.df - update_ds_editor() - - # Models - m.cur <<- workspace$m.cur - m <<- workspace$m - update_m.df() - m.gtable[,] <- m.df - update_m_editor() - - # Fits - f.cur <<- workspace$f.cur - f <<- workspace$f - s <<- workspace$s - if (length(f) > 0) { - update_f.df() - ftmp <<- f[[f.cur]] - stmp <<- s[[f.cur]] - ds.i <<- ds.cur - delete(f.gg.plotopts, f.gg.po.obssel) - f.gg.po.obssel <<- gcheckboxgroup(names(ftmp$mkinmod$spec), cont = f.gg.plotopts, - checked = TRUE) - update_plotting_and_fitting() - } else { - f.df <<- f.df.empty - update_ds_editor() - svalue(center) <- 1 - } - f.gtable[,] <- f.df + if (!is.na(ws$f)) { + f.df.ws <- data.frame(Name = names(ws$f), stringsAsFactors = FALSE) + f.df <- rbind(f.df, f.df.ws) } + f.df <<- f.df } -save_to_file_handler <- function(h, ...) -{ - studies.df <- data.frame(studies.gdf[,], stringsAsFactors = FALSE) - workspace <- list( - studies.df = studies.df, - - ds = ds, - ds.cur = ds.cur, - - m = m, - m.cur = m.cur, - - f = f, - f.cur = f.cur, - - s = s) - assign(project_name, workspace) - save(list = project_name, file = project_file) - svalue(sb) <- paste("Saved project contents to", project_file, "in working directory", getwd()) -} -change_project_name_handler = function(h, ...) { - project_name <<- as.character(svalue(h$obj)) - project_file <<- paste0(project_name, ".RData") -} -# Project data management GUI elements {{{2 -pr.gf <- gfile(text = "Select project file", cont = prg, - handler = upload_file_handler) -pr.ge <- gedit(project_name, cont = prg, label = "Project", - handler = change_project_name_handler) -# The save button is always visible {{{2 -gbutton("Save current project contents", cont = left, - handler = save_to_file_handler) - -# Widget and handler for Studies {{{1 -stg <- gexpandgroup("Studies", cont = left) -visible(stg) <- FALSE -update_study_selector <- function(h, ...) { - delete(ds.e.1, ds.study.gc) - ds.study.gc <<- gcombobox(paste("Study", studies.gdf[,1]), cont = ds.e.1) - svalue(ds.study.gc, index = TRUE) <- ds[[ds.cur]]$study_nr -} -studies.gdf <- gdf(studies.df, name = "Edit studies in the project", - width = 235, - height = 180, cont = stg) -studies.gdf$set_column_width(1, 40) -addHandlerChanged(studies.gdf, update_study_selector) -# Widgets and handlers for datasets and models {{{1 -dsm <- gframe("Datasets and models", cont = left, horizontal = FALSE) -# Widget for dataset table with handler {{{2 -ds.switcher <- function(h, ...) { - ds.cur <<- as.character(svalue(h$obj)) - update_ds_editor() +# Generate the initial workspace {{{1 +ws <- gmkinws$new() +ws.import <- NA +# Initialise meta data objects so assignments within functions using <<- will {{{2 +# update them in the right environment. +# Also create initial versions of meta data in order to be able to clear the workspace +p.df <- p.df.package <- data.frame(Name = c("FOCUS_2006", "FOCUS_2006_Z"), + Source = rep("gmkin package", 2), stringsAsFactors = FALSE) + +update_p.df() +ds.df <- ds.df.empty <- data.frame(Title = "", stringsAsFactors = FALSE) +m.df <- m.df.empty <- data.frame(Name = "", stringsAsFactors = FALSE) +f.df <- f.df.empty <- data.frame(Name = "", stringsAsFactors = FALSE) +ftmp <- NA +# left: Explorer tables {{{1 +# Frames {{{2 +p.gf <- gframe("Projects", cont = left, horizontal = FALSE) +ds.gf <- gframe("Datasets", cont = left) +m.gf <- gframe("Models", cont = left) +c.gf <- gframe("Configuration", cont = left, horizontal = FALSE) +f.gf <- gframe("Results", cont = left) + +# Project explorer {{{2 +# Initialize project list from the gmkin package and the current working directory +# The former must be manually amended if additional workspaces should be available +p.gtable <- gtable(p.df, cont = p.gf, width = left_width - 10, height = 120) +size(p.gtable) <- list(columnWidths = c(130, 100)) +p.switcher <- function(h, ...) { + p.cur <- h$row_index + Name <- p.df[p.cur, "Name"] + if (p.df[p.cur, "Source"] == "working directory") { + load(paste0(Name, ".gmkinws")) + ws <<- ws + } else { + ws <<- get(Name) + } svalue(center) <- 1 + svalue(c.ds) <- empty_conf_labels[1] + svalue(c.m) <- empty_conf_labels[2] + update_p_editor(p.cur) + update_ds.df() + ds.gtable[,] <<- ds.df + update_m.df() + m.gtable[,] <<- m.df + update_f.df() + f.gtable[,] <<- f.df } -ds.gtable <- gtable(ds.df, cont = dsm) -addHandlerDoubleClick(ds.gtable, ds.switcher) -size(ds.gtable) <- list(columnWidths = c(40, 150, 30)) -ds.gtable$value <- 1 - -# Model table with handler {{{2 -m.switcher <- function(h, ...) { - m.cur <<- as.character(svalue(h$obj)) - update_m_editor() +addHandlerClicked(p.gtable, p.switcher) +# Dataset explorer {{{2 +ds.switcher <- function(h, ...) { + ws$ds.cur <<- h$row_index + svalue(c.ds) <- ds.df[ws$ds.cur, "Title"] + #update_ds_editor() svalue(center) <- 2 } -m.gtable <- gtable(m.df, cont = dsm) -addHandlerDoubleClick(m.gtable, m.switcher) -m.gtable$set_column_width(1, 40) -m.gtable$value <- 1 - -# Button for setting up a fit for the selected dataset and model {{{2 -configure_fit_handler = function(h, ...) { - ds.i <<- as.character(svalue(ds.gtable)) - m.i <<- as.character(svalue(m.gtable)) - ftmp <<- suppressWarnings(mkinfit(m[[m.i]], - override(ds[[ds.i]]$data), - method.modFit = "Marq", - err = "err", - control.modFit = list(maxiter = 0))) - ftmp$ds.index <<- ds.i - ftmp$ds <<- ds[[ds.i]] - stmp <<- summary(ftmp) - svalue(pf) <- paste0("Dataset ", ds.i, ", Model ", m[[m.i]]$name) - svalue(f.gg.opts.plot) <<- FALSE - svalue(f.gg.opts.st) <<- ftmp$solution_type - svalue(f.gg.opts.weight) <<- ftmp$weight - svalue(f.gg.opts.atol) <<- ftmp$atol - svalue(f.gg.opts.rtol) <<- ftmp$rtol - svalue(f.gg.opts.transform_rates) <<- ftmp$transform_rates - svalue(f.gg.opts.transform_fractions) <<- ftmp$transform_fractions - svalue(f.gg.opts.reweight.method) <<- ifelse( - is.null(ftmp$reweight.method), - "none", ftmp$reweight.method) - svalue(f.gg.opts.reweight.tol) <<- ftmp$reweight.tol - svalue(f.gg.opts.reweight.max.iter) <<- ftmp$reweight.max.iter - svalue(f.gg.opts.method.modFit) <<- "Port" - svalue(f.gg.opts.maxit.modFit) <<- ftmp$maxit.modFit - f.gg.parms[,] <- get_Parameters(stmp, FALSE) - delete(f.gg.plotopts, f.gg.po.obssel) - f.gg.po.obssel <<- gcheckboxgroup(names(ftmp$mkinmod$spec), cont = f.gg.plotopts, - checked = TRUE) - show_plot("Initial", default = TRUE) - svalue(plot.ftmp.savefile) <<- paste(ftmp$ds$title, "_", ftmp$mkinmod$name, - ".", plot_format, sep = "") - oldwidth <<- options()$width - options(width = 90) - svalue(f.gg.summary.filename) <<- "" - svalue(f.gg.summary.listing) <<- c("
", capture.output(stmp), "
") - options(width = oldwidth) - svalue(center) <- 3 +ds.gtable <- gtable(ds.df, cont = ds.gf, width = left_width - 10, height = 160) +addHandlerClicked(ds.gtable, ds.switcher) +# Model explorer {{{2 +m.switcher <- function(h, ...) { + ws$m.cur <<- h$row_index + svalue(c.m) <- m.df[ws$m.cur, "Name"] + #update_m_editor() + svalue(center) <- 3 } -gbutton("Configure fit for selected model and dataset", cont = dsm, - handler = configure_fit_handler) - -# Widget and handler for fits {{{1 -f.gf <- gframe("Fits", cont = left, horizontal = FALSE) +m.gtable <- gtable(m.df, cont = m.gf, width = left_width - 10, height = 160) +addHandlerClicked(m.gtable, m.switcher) +# Fit explorer {{{2 f.switcher <- function(h, ...) { - if (svalue(h$obj) != 0) { - f.cur <<- svalue(h$obj) - ftmp <<- f[[f.cur]] - stmp <<- s[[f.cur]] - ds.i <<- ftmp$ds.index - update_plotting_and_fitting() + ws$f.cur <<- h$row_index - 1 + if (ws$f.cur > 0) { + ftmp <<- ws$f[[ws$f.cur]] + stmp <<- ws$s[[ws$f.cur]] + c.ds$call_Ext("setText", + paste0("", ftmp$ds$title, ""), FALSE) + c.m$call_Ext("setText", + paste0("", ftmp$m$name, ""), FALSE) } - svalue(center) <- 3 -} -f.gtable <- gtable(f.df, cont = f.gf) -addHandlerDoubleClick(f.gtable, f.switcher) -f.gtable$set_column_width(1, 40) -f.gtable$set_column_width(2, 60) - -# Dataset editor {{{1 -ds.editor <- gframe("Dataset 1", horizontal = FALSE, cont = center, - label = "Dataset editor") -# Handler functions {{{2 -ds.empty <- list( - study_nr = 1, - title = "", - sampling_times = c(0, 1), - time_unit = "", - observed = "parent", - unit = "", - replicates = 1, - data = data.frame( - name = "parent", - time = c(0, 1), - value = c(100, NA), - override = "NA", - err = 1, - stringsAsFactors = FALSE)) - -copy_dataset_handler <- function(h, ...) { - ds.old <- ds.cur - ds.cur <<- as.character(1 + length(ds)) - svalue(ds.editor) <- paste("Dataset", ds.cur) - ds[[ds.cur]] <<- ds[[ds.old]] - update_ds.df() - ds.gtable[,] <- ds.df -} - -delete_dataset_handler <- function(h, ...) { - if (length(ds) > 1) { - ds[[ds.cur]] <<- NULL - names(ds) <<- as.character(1:length(ds)) - ds.cur <<- names(ds)[[1]] - update_ds.df() - ds.gtable[,] <- ds.df - update_ds_editor() + #update_f_conf() + #update_f_results() + svalue(center) <- 5 +} +f.gtable <- gtable(f.df, cont = f.gf, width = left_width - 10, height = 160) +addHandlerClicked(f.gtable, f.switcher) +# Configuration {{{2 +empty_conf_labels <- paste0("Current ", c("dataset", "model"), "") +c.ds <- glabel(empty_conf_labels[1], cont = c.gf) +c.m <- glabel(empty_conf_labels[2], cont = c.gf) +c.conf <- gbutton("Configure fit", cont = c.gf, handler = function(h, ...) svalue(center) <- 4) +# center: Project editor {{{1 +p.editor <- gframe("", horizontal = FALSE, cont = center, + label = "Project") +# Working directory {{{2 +p.line.wd <- ggroup(cont = p.editor, horizontal = TRUE) +wd_handler <- function(h, ...) { + target_wd <- svalue(p.wde) + wd <- try(setwd(target_wd)) + if (inherits(wd, "try-error")) { + gmessage(paste("Could not set working directory to", target_wd), parent = w) + } else { + svalue(sb) <- paste("Changed working directory to", wd) + update_p.df() + p.gtable[,] <- p.df + p.line.import.p[,] <- c("", p.df$Name) + } +} +p.wde <- gedit(getwd(), cont = p.line.wd, label = "Working directory", width = 50) +p.wde$add_handler_enter(wd_handler) +p.wdb <- gbutton("Change", cont = p.line.wd, handler = wd_handler) +tooltip(p.wdb) <- "Edit the box on the left and press enter to change" +# Project name {{{2 +p.line.name <- ggroup(cont = p.editor, horizontal = TRUE) +p.name <- gedit("New project", label = "Project name", + width = 50, cont = p.line.name) +p.save <- gaction("Save", parent = w, + handler = function(h, ...) { + filename <- paste0(svalue(p.name), ".gmkinws") + try_to_save <- function (filename) { + if (!inherits(try(save(ws, file = filename)), + "try-error")) { + svalue(sb) <- paste("Saved project to file", filename, + "in working directory", getwd()) + update_p.df() + p.gtable[,] <- p.df + } else { + gmessage("Saving failed for an unknown reason", parent = w) + } + } + if (file.exists(filename)) { + gconfirm(paste("File", filename, "exists. Overwrite?"), + parent = w, + handler = function(h, ...) { + try_to_save(filename) + }) + } else { + try_to_save(filename) + } + }) +p.save.button <- gbutton(action = p.save, cont = p.line.name) +p.save$add_keybinding(save_keybinding) +tooltip(p.save.button) <- paste("Press", save_keybinding, "to save") + +update_p_editor <- function(p.cur) { + project_name <- as.character(p.df[p.cur, "Name"]) + svalue(p.name) <- project_name + if (p.df[p.cur, "Source"] == "gmkin package") { + svalue(p.filename) <- "" + p.delete$call_Ext("disable") } else { - galert("Deleting the last dataset is not supported", parent = w) + svalue(p.filename) <- file.path(getwd(), paste0(project_name, ".gmkinws")) + p.delete$call_Ext("enable") } } - -new_dataset_handler <- function(h, ...) { - ds.cur <<- as.character(1 + length(ds)) - ds[[ds.cur]] <<- ds.empty - update_ds.df() - ds.gtable[,] <- ds.df - update_ds_editor() -} - -tmptextheader <- character(0) -load_text_file_with_data <- function(h, ...) { - tmptextfile <<- normalizePath(svalue(h$obj), winslash = "/") - tmptext <- readLines(tmptextfile, warn = FALSE) - tmptextskip <<- 0 - for (tmptextline in tmptext) { - if (grepl(":|#|/", tmptextline)) tmptextskip <<- tmptextskip + 1 - else break() - } - svalue(ds.e.up.skip) <- tmptextskip - if (svalue(ds.e.up.header)) { - tmptextheader <<- strsplit(tmptext[tmptextskip + 1], - " |\t|;|,")[[1]] - } - svalue(ds.e.up.wide.time) <- tmptextheader[[1]] - svalue(ds.e.up.long.time) <- tmptextheader[[2]] - svalue(ds.e.up.text) <- c("
", tmptext, "
") - svalue(ds.e.stack) <- 2 -} - -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 <<- as.character(1 + length(ds)) - ds[[ds.cur]] <<- list( - study_nr = NA, - title = "New import", - sampling_times = sort(unique(tmpdl$time)), - time_unit = "", - observed = unique(tmpdl$name), - unit = "", - replicates = max(aggregate(tmpdl$time, - list(tmpdl$time, - tmpdl$name), - length)$x), - data = tmpdl) - ds[[ds.cur]]$data$override <<- as.numeric(NA) - if (is.null(ds[[ds.cur]]$data$err)) ds[[ds.cur]]$data$err <<- 1 +# File name {{{2 +p.line.file <- ggroup(cont = p.editor, horizontal = TRUE) +p.filename.gg <- ggroup(width = 400, cont = p.line.file) +p.filename <- glabel("", cont = p.filename.gg) +p.delete.handler = function(h, ...) { + filename <- file.path(getwd(), paste0(svalue(p.name), ".gmkinws")) + gconfirm(paste0("Are you sure you want to delete ", filename, "?"), + parent = w, + handler = function(h, ...) { + if (inherits(try(unlink(filename)), "try-error")) { + gmessage("Deleting failed for an unknown reason", cont = w) + } else { + svalue(sb) <- paste("Deleted", filename) + svalue(p.filename) <- "" + p.delete$call_Ext("disable") + update_p.df() + p.gtable[,] <- p.df + } + }) +} +p.delete <- gbutton("Delete", cont = p.line.file, + handler = p.delete.handler) +p.delete$call_Ext("disable") +# Import {{{2 +p.line.import <- ggroup(cont = p.editor, horizontal = TRUE) +p.line.import.p <- gcombobox(c("", p.df$Name), label = "Import from", cont = p.line.import, + handler = function(h, ...) { + p.import <- svalue(h$obj, index = TRUE) - 1 + Name <- p.df[p.import, "Name"] + if (p.df[p.import, "Source"] == "working directory") { + load(paste0(Name, ".gmkinws")) + ws.import <<- ws + } else { + ws.import <<- get(Name) + } + p.line.import.dst[,] <- data.frame(Title = sapply(ws.import$ds, function(x) x$title), + stringsAsFactors = FALSE) + p.line.import.mt[,] <- data.frame(Name = names(ws.import$m), + stringsAsFactors = FALSE) + }) +p.line.import.frames <- ggroup(cont = p.editor, horizontal = TRUE) + +p.line.import.dsf <- gframe("Datasets for import", cont = p.line.import.frames, horizontal = FALSE) +p.line.import.dst <- gtable(ds.df.empty, cont = p.line.import.dsf, multiple = TRUE, + width = left_width - 10, height = 160) +p.line.import.dsb <- gbutton("Import selected", cont = p.line.import.dsf, + handler = function(h, ...) { + i <- svalue(p.line.import.dst, index = TRUE) + ws$ds <<- append(ws$ds, ws.import$ds[i]) update_ds.df() ds.gtable[,] <- ds.df - update_ds_editor() - } else { - galert("Uploading failed", parent = "w") } -} - -empty_grid_handler <- function(h, ...) { - obs <- strsplit(svalue(ds.e.obs), ", ")[[1]] - sampling_times <- strsplit(svalue(ds.e.st), ", ")[[1]] - replicates <- as.numeric(svalue(ds.e.rep)) - new.data = data.frame( - name = rep(obs, each = replicates * length(sampling_times)), - time = as.numeric(rep(sampling_times, each = replicates, times = length(obs))), - value = as.numeric(NA), - override = as.numeric(NA), - err = 1, - stringsAsFactors = FALSE - ) - ds.e.gdf[,] <- new.data -} - -keep_ds_changes_handler <- function(h, ...) { - ds[[ds.cur]]$title <<- svalue(ds.title.ge) - ds[[ds.cur]]$study_nr <<- as.numeric(gsub("Study ", "", svalue(ds.study.gc))) - update_ds.df() - ds.gtable[,] <- ds.df - tmpd <- ds.e.gdf[,] - ds[[ds.cur]]$data <<- tmpd - ds[[ds.cur]]$sampling_times <<- sort(unique(tmpd$time)) - ds[[ds.cur]]$time_unit <<- svalue(ds.e.stu) - ds[[ds.cur]]$observed <<- unique(tmpd$name) - ds[[ds.cur]]$unit <<- svalue(ds.e.obu) - ds[[ds.cur]]$replicates <<- max(aggregate(tmpd$time, - list(tmpd$time, tmpd$name), length)$x) - update_ds_editor() - observed.all <<- union(observed.all, ds[[ds.cur]]$observed) - update_m_editor() -} - -# Widget setup {{{2 -# Line 1 {{{3 -ds.e.1 <- ggroup(cont = ds.editor, horizontal = TRUE) -glabel("Title: ", cont = ds.e.1) -ds.title.ge <- gedit(ds[[ds.cur]]$title, cont = ds.e.1) -glabel(" from ", cont = ds.e.1) -ds.study.gc <- gcombobox(paste("Study", studies.gdf[,1]), cont = ds.e.1) - -# Line 2 {{{3 -ds.e.2 <- ggroup(cont = ds.editor, horizontal = TRUE) -ds.e.2a <- ggroup(cont = ds.e.2, horizontal = FALSE) -gbutton("Copy dataset", cont = ds.e.2a, handler = copy_dataset_handler) -gbutton("Delete dataset", cont = ds.e.2a, handler = delete_dataset_handler) -gbutton("New dataset", cont = ds.e.2a, handler = new_dataset_handler) - -ds.e.2b <- ggroup(cont = ds.e.2) -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.e.2b, - handler = load_text_file_with_data) - -gbutton("Keep changes", cont = ds.e.2, handler = keep_ds_changes_handler) - -# Line 3 with forms or upload area {{{3 -ds.e.stack <- gstackwidget(cont = ds.editor) -# Forms for meta data {{{4 -ds.e.forms <- ggroup(cont = ds.e.stack, horizontal = TRUE) - -ds.e.3a <- gvbox(cont = ds.e.forms) -ds.e.3a.gfl <- gformlayout(cont = ds.e.3a) -ds.e.st <- gedit(paste(ds[[ds.cur]]$sampling_times, collapse = ", "), - width = 40, - label = "Sampling times", - cont = ds.e.3a.gfl) -ds.e.stu <- gedit(ds[[ds.cur]]$time_unit, - width = 20, - label = "Unit", cont = ds.e.3a.gfl) -ds.e.rep <- gedit(ds[[ds.cur]]$replicates, - width = 20, - label = "Replicates", cont = ds.e.3a.gfl) - -ds.e.3b <- gvbox(cont = ds.e.forms) -ds.e.3b.gfl <- gformlayout(cont = ds.e.3b) -ds.e.obs <- gedit(paste(ds[[ds.cur]]$observed, collapse = ", "), - width = 50, - label = "Observed", cont = ds.e.3b.gfl) -ds.e.obu <- gedit(ds[[ds.cur]]$unit, - width = 20, label = "Unit", - cont = ds.e.3b.gfl) -generate_grid.gb <- gbutton("Generate empty grid for kinetic data", cont = ds.e.3b, - handler = empty_grid_handler) -tooltip(generate_grid.gb) <- "Overwrites the kinetic data shown below" -# Data upload area {{{4 -ds.e.upload <- ggroup(cont = ds.e.stack, horizontal = TRUE) -ds.e.up.text <- ghtml("
", cont = ds.e.upload, width = 400, height = 400)
-ds.e.up.options <- ggroup(cont = ds.e.upload, horizontal = FALSE)
-ds.e.up.import <- gbutton("Import using options specified below", cont = ds.e.up.options,
-                          handler = new_ds_from_csv_handler)
-ds.e.up.skip <- gedit(tmptextskip, label = "Comment lines", 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,
-                         selected = 1, label = "Separator")
-ds.e.up.dec <- gcombobox(c(".", ","), cont = ds.e.up.options,
-                         selected = 1, label = "Decimal")
-ds.e.up.widelong <- gradio(c("wide", "long"), horizontal = TRUE, 
-                           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.up.options)
-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
-
-svalue(ds.e.stack) <- 1
-
-# Kinetic Data {{{3
-ds.e.gdf <- gdf(ds[[ds.cur]]$data, name = "Kinetic data", 
-                width = 500, height = 700, cont = ds.editor)
-ds.e.gdf$set_column_width(2, 70)
-
-# Update the dataset editor {{{3
-update_ds_editor <- function() {
-  svalue(ds.editor) <- paste("Dataset", ds.cur)
-  svalue(ds.title.ge) <- ds[[ds.cur]]$title
-  svalue(ds.study.gc, index = TRUE) <- ds[[ds.cur]]$study_nr
-
-  svalue(ds.e.st) <- paste(ds[[ds.cur]]$sampling_times, collapse = ", ")
-  svalue(ds.e.stu) <- ds[[ds.cur]]$time_unit
-  svalue(ds.e.obs) <- paste(ds[[ds.cur]]$observed, collapse = ", ")
-  svalue(ds.e.obu) <- ds[[ds.cur]]$unit
-  svalue(ds.e.rep) <- ds[[ds.cur]]$replicates
-  svalue(ds.e.stack) <- 1
-  ds.e.gdf[,] <- ds[[ds.cur]]$data
-}
-# Model editor {{{1
-m.editor <- gframe("Model 1", horizontal = FALSE, cont = center, label = "Model editor")
-# Handler functions {{{3
-copy_model_handler <- function(h, ...) {
-  m.old <- m.cur
-  m.cur <<- as.character(1 + length(m))
-  svalue(m.editor) <- paste("Model", m.cur)
-  m[[m.cur]] <<- m[[m.old]]
-  update_m.df()
-  m.gtable[,] <- m.df
-}
- 
-delete_model_handler <- function(h, ...) {
-  if (length(m) > 1) {
-    m[[m.cur]] <<- NULL
-    names(m) <<- as.character(1:length(m))
-    m.cur <<- "1"
+)
+
+p.line.import.mf <- gframe("Models for import", cont = p.line.import.frames, horizontal = FALSE)
+p.line.import.mt <- gtable(m.df.empty, cont = p.line.import.mf, multiple = TRUE,
+                            width = left_width - 10, height = 160)
+p.line.import.mb <- gbutton("Import selected", cont = p.line.import.mf,
+  handler = function(h, ...) {
+    i <- svalue(p.line.import.mt, index = TRUE)
+    ws$m <<- append(ws$m, ws.import$m[i])
     update_m.df()
     m.gtable[,] <- m.df
-    update_m_editor()
-  } else {
-    galert("Deleting the last model is not supported", parent = w)
-  }
-}
-
-add_observed_handler <- function(h, ...) {
-  obs.i <- length(m.e.rows) + 1
-  m.e.rows[[obs.i]] <<- ggroup(cont = m.editor, horizontal = TRUE)
-  m.e.obs[[obs.i]] <<- gcombobox(observed.all, selected = obs.i, 
-                                cont = m.e.rows[[obs.i]])
-  m.e.type[[obs.i]] <<- gcombobox(c("SFO", "SFORB"),
-                                 cont = m.e.rows[[obs.i]])
-  svalue(m.e.type[[obs.i]]) <- "SFO"
-  glabel("to", cont = m.e.rows[[obs.i]]) 
-  m.e.to[[obs.i]] <<- gedit("",
-                            initial.msg = "Optional list of target variables, e.g. 'm1, m2'",
-                            width = 40, cont = m.e.rows[[obs.i]])
-  m.e.sink[[obs.i]] <<- gcheckbox("Path to sink", 
-                                  checked = TRUE, cont = m.e.rows[[obs.i]]) 
-  gbutton("Remove compound", handler = remove_observed_handler, 
-          action = obs.i, cont = m.e.rows[[obs.i]])
-}
-
-remove_observed_handler <- function(h, ...) {
-  m[[m.cur]]$spec[[h$action]] <<- NULL
-  update_m_editor()
-}
-
-keep_m_changes_handler <- function(h, ...) {
-  spec <- list()
-  for (obs.i in 1:length(m.e.rows)) {
-    to_vector = strsplit(svalue(m.e.to[[obs.i]]), ", ")[[1]]
-    if (length(to_vector) == 0) to_vector = ""
-    spec[[obs.i]] <- list(type = svalue(m.e.type[[obs.i]]),
-                          to = to_vector,
-                          sink = svalue(m.e.sink[[obs.i]]))
-    if(spec[[obs.i]]$to[[1]] == "") spec[[obs.i]]$to = NULL
-    names(spec)[[obs.i]] <- svalue(m.e.obs[[obs.i]])
-  }
-  m[[m.cur]] <<- mkinmod(use_of_ff = svalue(m.ff.gc), 
-                         speclist = spec)
-  m[[m.cur]]$name <<- svalue(m.name.ge) 
-  update_m.df()
-  m.gtable[,] <- m.df
-}
- 
-# Widget setup {{{3
-m.e.0 <- ggroup(cont = m.editor, horizontal = TRUE)
-glabel("Model name: ", cont = m.e.0) 
-m.name.ge <- gedit(m[[m.cur]]$name, cont = m.e.0) 
-glabel("Use of formation fractions: ", cont = m.e.0) 
-m.ff.gc <- gcombobox(c("min", "max"), cont = m.e.0)
-svalue(m.ff.gc) <- m[[m.cur]]$use_of_ff
-
-# Model handling buttons {{{4
-m.e.b <- ggroup(cont = m.editor, horizontal = TRUE)
-gbutton("Copy model", cont = m.e.b, handler = copy_model_handler)
-gbutton("Delete model", cont = m.e.b, handler = delete_model_handler)
-gbutton("Add observed variable", cont = m.e.b, 
-        handler = add_observed_handler)
-gbutton("Keep changes", cont = m.e.b, handler = keep_m_changes_handler)
-
-
-m.observed <- names(m[[m.cur]]$spec)
-m.e.rows <- m.e.obs <- m.e.type <- m.e.to <- m.e.sink <- list()
-obs.to <- ""
-
-# Show the model specification {{{4
-show_m_spec <- function() {
-  for (obs.i in 1:length(m[[m.cur]]$spec)) {
-    obs.name <- names(m[[m.cur]]$spec)[[obs.i]]
-    m.e.rows[[obs.i]] <<- ggroup(cont = m.editor, horizontal = TRUE)
-    m.e.obs[[obs.i]] <<- gcombobox(observed.all, selected = 0, 
-                                  cont = m.e.rows[[obs.i]])
-    svalue(m.e.obs[[obs.i]]) <<- obs.name
-    if (obs.i == 1) {
-      m.e.type[[obs.i]] <<- gcombobox(c("SFO", "FOMC", "DFOP", "HS", "SFORB"),
-                                     cont = m.e.rows[[obs.i]])
-    } else {
-      m.e.type[[obs.i]] <<- gcombobox(c("SFO", "SFORB"),
-                                     cont = m.e.rows[[obs.i]])
-    }
-    svalue(m.e.type[[obs.i]]) <<- m[[m.cur]]$spec[[obs.i]]$type
-    glabel("to", cont = m.e.rows[[obs.i]]) 
-    obs.to <<- ifelse(is.null(m[[m.cur]]$spec[[obs.i]]$to), "",
-                 paste(m[[m.cur]]$spec[[obs.i]]$to, collapse = ", "))
-    m.e.to[[obs.i]] <<- gedit(obs.to, 
-                              initial.msg = "Optional list of target variables, e.g. 'm1, m2'",
-                              width = 40, cont = m.e.rows[[obs.i]])
-    m.e.sink[[obs.i]] <<- gcheckbox("Path to sink", checked = m[[m.cur]]$spec[[obs.i]]$sink,
-              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]])
-    }
-  }
-}
-show_m_spec()
-
-# Update the model editor {{{3
-update_m_editor <- function() {
-  svalue(m.editor) <- paste("Model", m.cur)
-  svalue(m.name.ge) <- m[[m.cur]]$name
-  svalue(m.ff.gc) <- m[[m.cur]]$use_of_ff
-  for (oldrow.i in 1:length(m.e.rows)) {
-    delete(m.editor, m.e.rows[[oldrow.i]])
-  }
-  m.observed <<- names(m[[m.cur]]$spec)
-  m.e.rows <<- m.e.obs <<- m.e.type <<- m.e.to <<- m.e.sink <<- list()
-  show_m_spec()
-}
-
-# 3}}}
-# 2}}}
-# Plotting and fitting {{{1
-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()
-}
-get_Parameters <- function(stmp, optimised)
-{
-  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)
-}
-run_fit <- function() {
-  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), "
") -} -ds.i <- m.i <- "1" -f.cur <- "0" +) + + +# center: Dataset editor {{{1 +ds.editor <- gframe("", horizontal = FALSE, cont = center, + label = "Dataset editor") +m.editor <- gframe("", horizontal = FALSE, cont = center, + label = "Model editor") +f.config <- gframe("", horizontal = FALSE, cont = center, + label = "Fit configuration") +r.viewer <- gframe("", horizontal = FALSE, cont = center, + label = "Result viewer") +svalue(center) <- 1 +# right: Viewing area {{{1 +# Workflow {{{2 +workflow.gg <- ggroup(cont = right, label = "Workflow", width = 480, height = 600, + 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) + +# 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("
+ +", paste(gmkin_manual_body, collapse = '\n'), " +
"), width = 460, cont = right) + +# Changes {{{2 +gmkin_news <- markdownToHTML(system.file("NEWS.md", package = "gmkin"), + fragment.only = TRUE, + ) + +changes.gh <- ghtml(label = "Changes", paste0("
+ +", gmkin_news, " +
"), width = 460, cont = right) + +svalue(right) <- 1 -# GUI widgets {{{2 -pf <- gframe("Dataset 1, Model SFO", horizontal = TRUE, - cont = center, label = "Plotting and fitting") -# Plot area to the left {{{3 -pf.p <- ggroup(cont = pf, horizontal = FALSE) -ftmp <- suppressWarnings(mkinfit(m[[m.cur]], override(ds[[ds.i]]$data), - err = "err", - method.modFit = "Marq", - control.modFit = list(maxiter = 0))) -ftmp$ds.index = ds.i -ftmp$ds = ds[[ds.i]] -stmp <- summary(ftmp) -Parameters <- get_Parameters(stmp, FALSE) - -plot_ftmp <- function() { - if(exists("f.gg.po.obssel")) { - obs_vars_plot = svalue(f.gg.po.obssel) - } else { - obs_vars_plot = names(ftmp$mkinmod$spec) - } - if(exists("f.gg.po.legend")) { - plot_legend = svalue(f.gg.po.legend) - } else { - plot_legend = TRUE - } - plot(ftmp, main = ftmp$ds$title, obs_vars = obs_vars_plot, - xlab = ifelse(ftmp$ds$time_unit == "", "Time", - paste("Time in", ftmp$ds$time_unit)), - ylab = ifelse(ds[[ds.i]]$unit == "", "Observed", - paste("Observed in", ftmp$ds$unit)), - legend = plot_legend, - show_residuals = TRUE) -} - -plot_ftmp_png <- function() { - tf <- get_tempfile(ext=".png") - png(tf, width = 400, height = 400) - plot_ftmp() - dev.off() - return(tf) -} - -plot_ftmp_save <- function(filename) { - switch(plot_format, - png = png(filename, width = 400, height = 400), - pdf = pdf(filename), - wmf = win.metafile(filename)) - plot_ftmp() - dev.off() - svalue(sb) <- paste("Saved plot to", filename, "in working directory", getwd()) -} - -plot_confint_png <- function() { - tf <- get_tempfile(ext=".png") - png(tf, width = 400, height = 400) - mkinparplot(ftmp) - dev.off() - return(tf) -} - -plot_formats <- c("png", "pdf") -if (exists("win.metafile", "package:grDevices", inherits = FALSE)) { - plot_formats = c("wmf", plot_formats) -} -plot_format <- plot_formats[[1]] - -plot.ftmp.gi <- gimage(plot_ftmp_png(), container = pf.p, width = 400, height = 400) -plot.ftmp.saveline <- ggroup(cont = pf.p, horizontal = TRUE) -plot.ftmp.savefile <- gedit(paste(ds[[ds.cur]]$title, "_", m[[m.cur]]$name, ".", - plot_format, sep = ""), - width = 40, cont = plot.ftmp.saveline) -plot.ftmp.savebutton <- gbutton("Save plot", cont = plot.ftmp.saveline, - handler = function(h, ...) { - filename <- svalue(plot.ftmp.savefile) - if (file.exists(filename)) - { - gconfirm(paste("File", filename, - "exists. Overwrite?"), - parent = w, - handler = function(h, ...) { - plot_ftmp_save(filename) - } - ) - } else { - plot_ftmp_save(filename) - } - }) -plot.space <- ggroup(cont = pf.p, horizontal = TRUE, height = 18) -plot.confint.gi <- gimage(plot_confint_png(), container = pf.p, width = 400, height = 400) - -# Buttons and notebook area to the right {{{3 -p.gg <- ggroup(cont = pf, horizontal = FALSE) -# Row with buttons {{{4 -f.gg.buttons <- ggroup(cont = p.gg) -run.fit.gb <- gbutton("Run", width = 100, - handler = function(h, ...) run_fit(), cont = - f.gg.buttons) -tooltip(run.fit.gb) <- "Fit with current settings on the current dataset, with the original model" - -keep.fit.gb <- gbutton("Keep fit", - handler = function(h, ...) { - 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) - }, cont = f.gg.buttons) -tooltip(keep.fit.gb) <- "Store the optimised model with all settings and the current dataset in the fit list" - -delete_fit_handler <- function(h, ...) { - if (length(f) > 0) { - f[[f.cur]] <<- NULL - s[[f.cur]] <<- NULL - } - if (length(f) > 0) { - names(f) <<- as.character(1:length(f)) - names(s) <<- as.character(1:length(f)) - update_f.df() - f.cur <<- "1" - ftmp <<- f[[f.cur]] - stmp <<- s[[f.cur]] - ds.i <<- ftmp$ds.index - update_plotting_and_fitting() - } else { - f.df <<- f.df.empty - f.cur <<- "0" - } - f.gtable[,] <<- f.df -} - -delete.fit.gb <- gbutton("Delete fit", handler = delete_fit_handler, - cont = f.gg.buttons) -tooltip(delete.fit.gb) <- "Delete the currently loaded fit from the fit list" - -show.initial.gb <- gbutton("Show initial", - handler = function(h, ...) show_plot("Initial"), - cont = f.gg.buttons) -tooltip(show.initial.gb) <- "Show model with current inital settings for current dataset" - -get_initials_handler <- function(h, ...) -{ - f.i <- svalue(get.initials.gc, index = TRUE) - if (length(f) > 0) { - got_initials <- c(f[[f.i]]$bparms.fixed, f[[f.i]]$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 initials from", cont = f.gg.buttons, - handler = get_initials_handler) -get.initials.gc <- gcombobox(paste("Fit", f.df$Fit), cont = f.gg.buttons) - -# Notebook to the right {{{3 -f.gn <- gnotebook(cont = p.gg, width = 680, height = 790) -# Dataframe with initial and optimised parameters {{{4 -f.gg.parms <- gdf(Parameters, cont = f.gn, - width = 670, height = 750, - do_add_remove_buttons = FALSE, label = "Parameters") -f.gg.parms$set_column_width(1, 200) -f.gg.parms$set_column_width(2, 50) -f.gg.parms$set_column_width(3, 60) -f.gg.parms$set_column_width(4, 50) -f.gg.parms$set_column_width(5, 60) - -# Fit options form {{{4 -f.gg.opts <- gformlayout(cont = f.gn, label = "Fit options") -solution_types <- c("auto", "analytical", "eigen", "deSolve") -f.gg.opts.plot <- gcheckbox("plot", - cont = f.gg.opts, checked = FALSE) -f.gg.opts.st <- gcombobox(solution_types, selected = 1, - label = "solution_type", width = 200, - cont = f.gg.opts) -f.gg.opts.atol <- gedit(ftmp$atol, label = "atol", width = 20, - cont = f.gg.opts) -f.gg.opts.rtol <- gedit(ftmp$rtol, label = "rtol", width = 20, - cont = f.gg.opts) -f.gg.opts.transform_rates <- gcheckbox("transform_rates", - cont = f.gg.opts, checked = TRUE) -f.gg.opts.transform_fractions <- gcheckbox("transform_fractions", - cont = f.gg.opts, checked = TRUE) -weights <- c("manual", "none", "std", "mean") -f.gg.opts.weight <- gcombobox(weights, selected = 1, label = "weight", - width = 200, cont = f.gg.opts) -f.gg.opts.reweight.method <- gcombobox(c("none", "obs"), selected = 1, - label = "reweight.method", - width = 200, - cont = f.gg.opts) -f.gg.opts.reweight.tol <- gedit(1e-8, label = "reweight.tol", - width = 20, cont = f.gg.opts) -f.gg.opts.reweight.max.iter <- gedit(10, label = "reweight.max.iter", - width = 20, cont = f.gg.opts) -optimisation_methods <- c("Port", "Marq", "SANN") -f.gg.opts.method.modFit <- gcombobox(optimisation_methods, selected = 1, - label = "method.modFit", - width = 200, - cont = f.gg.opts) -f.gg.opts.maxit.modFit <- gedit("auto", label = "maxit.modFit", - width = 20, cont = f.gg.opts) - -# Summary {{{3 -oldwidth <- options()$width -options(width = 90) -f.gg.summary <- ggroup(label = "Summary", cont = f.gn, horizontal = FALSE) -f.gg.summary.topline <- ggroup(cont = f.gg.summary, horizontal = TRUE) -f.gg.summary.filename <- gedit(paste(ds[[ds.cur]]$title, "_", m[[m.cur]]$name, - ".txt", sep = ""), - width = 50, 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(stmp, file = filename) - } - }) -f.gg.summary.listing <- ghtml(c("
", capture.output(stmp), "
"), - cont = f.gg.summary, label = "Summary") -options(width = oldwidth) - -# Plot options {{{4 -f.gg.plotopts <- ggroup(cont = f.gn, label = "Plot options", horizontal = FALSE, - width = 200) - -f.gg.po.format <- gcombobox(plot_formats, selected = 1, label = "File format", - cont = f.gg.plotopts, - 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.update <- gbutton("Update plot", - handler = function(h, ...) show_plot("Optimised"), - cont = f.gg.plotopts) -f.gg.po.obssel <- gcheckboxgroup(names(m[[m.cur]]$spec), cont = f.gg.plotopts, - checked = TRUE) -svalue(f.gn) <- 1 - -# Update the plotting and fitting area {{{3 -update_plotting_and_fitting <- function() { - svalue(pf) <- paste0("Fit ", f.cur, ": Dataset ", ftmp$ds.index, - ", Model ", ftmp$mkinmod$name) - # Parameters - f.gg.parms[,] <- get_Parameters(stmp, TRUE) - - # Fit options - delete(f.gg.buttons, get.initials.gc) - get.initials.gc <<- gcombobox(paste("Fit", f.df$Fit), cont = f.gg.buttons) - - svalue(f.gg.opts.st) <- ftmp$solution_type - svalue(f.gg.opts.atol) <- ftmp$atol - svalue(f.gg.opts.rtol) <- ftmp$rtol - svalue(f.gg.opts.transform_rates) <- ftmp$transform_rates - svalue(f.gg.opts.transform_fractions) <- ftmp$transform_fractions - svalue(f.gg.opts.weight) <- ftmp$weight.ini - svalue(f.gg.opts.reweight.method) <- ifelse(is.null(ftmp$reweight.method), - "none", - ftmp$reweight.method) - svalue(f.gg.opts.reweight.tol) <- ftmp$reweight.tol - svalue(f.gg.opts.reweight.max.iter) <- ftmp$reweight.max.iter - svalue(f.gg.opts.method.modFit) <- ftmp$method.modFit - svalue(f.gg.opts.maxit.modFit) <- ftmp$maxit.modFit - - # Summary - oldwidth <<- options()$width - options(width = 90) - svalue(f.gg.summary.filename) <<- paste(ftmp$ds$title, "_", ftmp$mkinmod$name, ".txt", sep = "") - svalue(f.gg.summary.listing) <<- c("
", capture.output(stmp), "
") - options(width = oldwidth) - - # Plot options - delete(f.gg.plotopts, f.gg.po.obssel) - f.gg.po.obssel <<- gcheckboxgroup(names(ftmp$mkinmod$spec), cont = f.gg.plotopts, - checked = TRUE) - # Plot - svalue(plot.ftmp.savefile) <<- paste(ftmp$ds$title, "_", ftmp$mkinmod$name, - ".", plot_format, sep = "") - show_plot("Optimised") - -} # vim: set foldmethod=marker ts=2 sw=2 expandtab: {{{1 diff --git a/inst/GUI/gmkin_manual.html b/inst/GUI/gmkin_manual.html new file mode 100644 index 0000000..588f580 --- /dev/null +++ b/inst/GUI/gmkin_manual.html @@ -0,0 +1,233 @@ + + + + + + + Manual for gmkin + + + + + + + +

Introduction

+

The R add-on package gmkin provides a browser based graphical interface for performing kinetic evaluations of degradation data using the mkin package. While the use of gmkin should be largely self-explanatory, this manual may serve as a functionality overview and reference.

+

For system requirements and installation instructions, please refer to the gmkin homepage

+

Starting gmkin

+

As gmkin is an R package, you need to start R and load the gmkin package before you can run gmkin. This can be achieved by entering the command

+
library(gmkin)
+

into the R console. This will also load the packages that gmkin depends on, most notably gWidgetsWWW2 and mkin. Loading the package only has to be done once after you have started R.

+

Before you start gmkin, you should make sure that R is using the working directory that you would like to keep your gmkin project file(s) in. If you use the standard R application on windows, you can change the working directory from the File menu.

+

Once you are sure that the working directory is what you want it to be, gmkin can be started by entering the R command

+
gmkin()
+

This will cause the default browser to start up or, if it is already running, to pop up and open a new tab for displaying the gmkin user interface.

+

In the R console, you should see some messages, telling you if the local R help server, which also serves the gmkin application, has been started, which port it is using and that it is starting an app called gmkin.

+

Finally, it should give a message like

+
Model cost at call 1: 2388.077
+

which means that the first kinetic evaluation has been configured for fitting.

+

In the browser, you should see something like the screenshot below.

+
+gmkin start +

gmkin start

+
+

The statusbar at the bottom of the gmkin window shows, among others, the working directory that gmkin uses.

+

Note that the project file management area described below can be minimized by clicking on the arrows on the right hand side of its title bar. This may be helpful if the vertical size of your browser window is restricted.

+

Project file management

+

At startup, gmkin loads a project called "FOCUS_2006_gmkin" which is distributed with the gmkin package. A gmkin project contains datasets, kinetic models for fitting, and so-called fits, i.e. the results of fitting models to data. These gmkin projects can be saved and restored using the project file management area in the top left.

+
+projects +

projects

+
+

If you would like to save these items for reference or for the purpose of continuing your work at a later time, you can modify the project name and press the button below it. The full name of the project file created and the working directory will be displayed in the gmkin status bar.

+

For restoring a previously saved project file, use the Browse button to locate it, and the "Upload" button to load its contents into gmkin.

+

Studies

+

The "Studies" area directly below the "Project file management" area can be expanded by clicking on the arrows on the right hand side of its title bar. Studies in gmkin are simply a numbered list of sources for the datasets in a project. You can edit the titles directly by clicking on them. If you would like to add a new data source, use the "Add" button above the table containing the list. If there are more than one studies in the list, you can also remove them using the "Remove" button.

+
+studies +

studies

+
+

Note that the user is responsible to keep the study list consistent with the numbers that are used in the list of datasets described below.

+

Datasets and Models

+

The project loaded at the start of gmkin contains two datasets and four kinetic models. These are listed to the left under the heading "Datasets and Models", together with a button for setting up fits as shown below.

+
+datasets and models +

datasets and models

+
+

For editing, adding or removing datasets or models, you need to double-click on an entry in the respective list.

+

For setting up a fit of a specific model to a specific dataset, the model and the dataset should be selected by clicking on them. If they are compatible, clicking the button "Configure fit for selected dataset and model" will set up the fit and open the "Plotting and Fitting" tab to the right.

+

Dataset editor

+

The dataset editor allows for editing datasets, entering new datasets, uploading data from text files and deleting datasets.

+
+dataset editor +

dataset editor

+
+

If you want to create (enter or load) a new dataset, it is wise to first edit the list of data sources in the "Studies" area as described above.

+

Entering data directly

+

For entering new data manually, click on "New dataset", enter a title and select the study from which the dataset is taken. At this stage, you may already want to press "Keep changes", so the dataset appears in the list of datasets.

+

In order to generate a table suitable for entering the data, enter a comma separated list of sampling times, optionally the time unit, and the number of replicate measurements at each sampling time. Also, add a comma separated list of short names of the relevant compounds in your dataset. A unit can be specified for the observed values. An example of filling out the respective fields is shown below.

+
+generate data grid +

generate data grid

+
+

Once everyting is filled out to your satisfaction, press the button "Generate empty grid for kinetic data". In our example, this would result in the data grid shown below. You can enter the observed data into the value column, as shown in the screenshot below.

+
+data grid +

data grid

+
+

The column with title override serves to override data points from the original datasets, without loosing the information which value was originally reported.

+

If everything is OK, press "Keep changes" to save the dataset in the current workspace. Note that you need to save the project file (see above) in order to be able to use the dataset that you created in a future gmkin session.

+

Importing data from text files

+

In case you want to work with a larger dataset that is already available as a computer file e.g. in a spreadsheet application, you can export these data as a tab separated or comma separated text file and import it using the "Browse" and "Upload" buttons in the dataset editor.

+

As an example, we can create a text file from one of the datasets shipped with the mkin package using the following R command:

+
write.table(schaefer07_complex_case, sep = ",", dec = ".", 
+            row.names = FALSE, quote = FALSE, 
+            file = "schaefer07.csv")
+

This produces a text file with comma separated values in the current working directory of R.

+

Loading this text file into gmkin using the "Browse" and "Upload" buttons results in an import configuration area like this, with the uploaded text file displayed to the left, and the import options to the right.

+
+upload area +

upload area

+
+

In the import configuration area, the following options can be specified. In the field "Comment lines", the number of lines in the beginning of the file that should be ignored can be specified.

+

The checkbox on the next line should be checked if the first line of the file contains the column names, i.e. the names of the observed variables when the data are in wide format.

+

As "Separator", whitespace, semicolon or comma can be chosen. If whitespace is selected, files in which the values are separated by a fixed or varying number of whitespace characters should be read in correctly. As the tabulator counts as a whitespace character, this is also the option to choose for tabulator separated values.

+

As the "Decimal" separator, comma "," or period "." can be selected.

+

In the next line, it can be specified if the data are in wide or in long format. If in wide format, the only option left to specify is the title of the column containing the sampling times. If the data is in long format, the column headings specifying the columns containing the observed variables (default is "name"), the sampling times (default is "time"), the observed values (default is "value") and, if present in the data, the relative errors (default is "err") can be adapted. The default settings appearing if the long format is selected are shown below.

+
+long +

long

+
+

In our example we have data in the wide format, and after adapting the "Separator" to a comma, we can press the button "Import using options specified below", and the data should be imported. If successful, the data editor should show the sampling times and the names of the observed variables, as well as the imported data in a grid for further editing or specifying overrides.

+

After editing the title of the dataset and selecting the correct study as the source of the data, the dataset editor should look like shown below.

+
+successful upload +

successful upload

+
+

If everything is OK, press "Keep changes" to save the dataset in the current workspace. Again, you need to save the project file in order to be able to use the dataset that you created in a future gmkin session.

+

Model editor

+

The following screenshot shows the model editor for the model number 4 in the list of models that are in the initial workspace.

+
+model editor +

model editor

+
+

In the first line the name of the model can be edited. You can also specify "min" or "max" for minimum or maximum use of formation fractions. Maximum use of formation fractions means that the differential equations in the degradation model are formulated using formation fractions. When you specify "min", then formation fractions are only used for the parent compound when you use the FOMC, DFOP or the HS model for it.

+

Pressing "Copy model" keeps the model name, so you should change it for the newly generated copy. Pressing "Add observed variable" adds a line in the array of state variable specifications below. The observed variables to be added are usually transformation products (usually termed metabolites), but can also be the parent compound in a different compartment (e.g. "parent_sediment").

+

Only observed variable names that occur in previously defined datasets can be selected. For any observed variable other than the first one, only the SFO or the SFORB model can be selected. For each observed variables, a comma separated list of target variables can be specified. In addition, a pathway to the sink compartment can be selected. If too many observed variables have been added, complete lines can be removed from the model definition by pressing the button "Remove observed variable".

+

If the model definition is supposedly correct, press "Keep changes" to make it possible to select it for fitting in the listing of models to the left.

+

Plotting and fitting

+

If the dataset(s) to be used in a project are created, and suitable kinetic models have been defined, kinetic evaluations can be configured by selecting one dataset and one model in the lists to the left, and the pressing the button "Configure fit for selected dataset and model" below these lists.

+

This opens the "Plotting and fitting" tab area to the right, consisting of a graphical window showing the data points in the selected dataset and the model, evaluated with the initial parameters defined by calling mkinfit without defining starting parameters. The value of the objective function to be minimized for these default parameters can be seen in the R console, e.g. as

+
Model cost at call 1: 15156.12
+

for the example shown below, where the FOCUS example dataset D and the model SFO_SFO were selected.

+
+plotting and fitting +

plotting and fitting

+
+

Parameters

+

In the right hand area, initially the tab with the parameter list is displayed. While name and type of the parameters should not be edited, their initial values can be edited by clicking on a row. Also, it can be specified if the parameters should be fixed in the optimisation process.

+

If the initial values for the parameters were changed, the resulting model solution can be visually checked by pressing the button "Show initial". This will update the plot of the model and the data using the specified initial parameter values.

+

If a similar model with a partially overlapping model definition has already be fitted, initial values for parameters with the same name in both models can also be retrieved from previous fits by selecting the fit and pressing the button "Get initials from". This facilitates stepwise fitting of more complex degradation pathways.

+

After the model has been successfully fitted by pressing the "Run" button, the optimised parameter values are added to the parameter table.

+

Fit options

+

The most important fit options of the mkinfit function can be set via the "Fit option" tab shown below. If the "plot" checkbox is checked, an R graphics device started via the R console shows the fitting progress, i.e. the change of the model solution together with the data during the optimisation.

+
+fit options +

fit options

+
+

The "solution_type" can either be "auto", which means that the most effective solution method is chosen for the model, in the order of "analytical" (for parent only degradation data), "eigen" (for differential equation models with only linear terms, i.e. without FOMC, DFOP or HS submodels) or "deSolve", which can handle all model definitions generated by the mkin package.

+

The parameters "atol" and "rtol" are only effective if the solution type is "deSolve". They control the precision of the iterative numerical solution of the differential equation model.

+

The checkboxes "transform_rates" and "transform_fractions" control if the parameters are fitted as defined in the model, or if they are internally transformed during the fitting process in order to improve the estimation of standard errors and confidence intervals which are based on a linear approximation at the optimum found by the fitting algorithm.

+

If fitting with transformed fractions leads to a suboptimal fit, doing a first run without transforming fractions may help. A final run using the optimised parameters from the previous run as starting values (see comment on "Get initials from" above) can then be performed with transformed fractions.

+

The dropdown box "weight" specifies if and how the observed values should be weighted in the fitting process. If "manual" is chosen, the values in the "err" column of the dataset are used, which are set to unity by default. Setting these to higher values gives lower weight and vice versa. If "none" is chosen, observed values are not weighted. Please refer to the documentation of the modFit function from the FME package for the meaning of options "std" and "mean".

+

The options "reweight.method", "reweight.tol" and "reweight.max.iter" enable the use of iteratively reweighted least squares fitting, if the reweighting method is set to "obs". Please refer to the mkinfit documentation for more details.

+

The drop down box "method.modFit" makes it possible to choose between the optimisation algorithms "Port" (the default in mkin versions > 0.9-33, a local optimisation algorithm using a model/trust region approach), "Marq" (the former default in mkin, a Levenberg-Marquardt variant from the R package minpack.lm), and "SANN" (the simulated annealing method - robust but inefficient and without a convergence criterion).

+

Finally, the maximum number of iterations for the optimisation can be adapted using the "maxit.modFit" field.

+

Fitting the model

+

In many cases the starting parameters and the fit options do not need to be modified and the model fitting process can simply be started by pressing the "Run" button. In the R console, the progressive reduction in the model cost can be monitored and will be displayed like this:

+
Model cost at call  1 :  15156.12 
+Model cost at call  3 :  15156.12 
+Model cost at call  7 :  14220.79 
+Model cost at call  8 :  14220.79 
+Model cost at call  11 :  14220.79 
+Model cost at call  12 :  3349.268 
+Model cost at call  15 :  3349.268 
+Model cost at call  17 :  788.6367 
+Model cost at call  18 :  788.6366 
+Model cost at call  22 :  374.0575 
+Model cost at call  23 :  374.0575 
+Model cost at call  27 :  371.2135 
+Model cost at call  28 :  371.2135 
+Model cost at call  32 :  371.2134 
+Model cost at call  36 :  371.2134 
+Model cost at call  37 :  371.2134 
+

If plotting of the fitting progress was selecte in the "Fit options" tab, a new separate graphics window should either pop up, or a graphics window previously started for this purpose will be reused.

+

Summary

+

Once a fit has successfully been performed by pressing the "Run" button, the summary as displayed below can be accessed via the "Summary" tab.

+
+summary +

summary

+
+

The complete summary can be saved into a text file by specifying a suitable file name and pressing the button "Save summary".

+

Plot options

+

In the tab "Plot options", the file format can be chosen, the legend can be turned off, and the observed variables for which the data and the model fit should be plotted can be selected as shown below.

+
+plot options +

plot options

+
+

On systems running the Windows operating system, the windows metafile (wmf) format can be additionally chosen. Chaning the file format for plotting will also change the extension of the proposed filename for saving the plot.

+

Confidence interval plots

+

Whenever a new fit has been configured or a run of a fit has been completed, the plotting area is updated with the abovementioned plot of the data and the current model solution.

+

In addition, a confidence interval plot is shown below this conventional plot. In case a fit has been run and confidence intervals were successfully calculated for the fit (i.e. if the model was not overparameterised and no other problems occurred), the confidence intervals are graphically displayed as bars as shown below.

+
+confidence +

confidence

+
+ + + diff --git a/inst/GUI/gmkin_workflow_434x569.png b/inst/GUI/gmkin_workflow_434x569.png new file mode 100644 index 0000000..a18f48f Binary files /dev/null and b/inst/GUI/gmkin_workflow_434x569.png differ diff --git a/inst/GUI/gmkin_workflow_inkscape.svg b/inst/GUI/gmkin_workflow_inkscape.svg new file mode 100644 index 0000000..0d7275b --- /dev/null +++ b/inst/GUI/gmkin_workflow_inkscape.svg @@ -0,0 +1,556 @@ + +image/svg+xmlProject management:Load or save project files +Dataset management:Load, create, edit, move or delete datasets +Model management:Select, create, edit, move or delete models +Fit configuration:Combine model with data, set fit options and start the fit +Result viewer:Check graphs and statistics, view endpoints, save or delete fits + \ No newline at end of file diff --git a/man/FOCUS_2006.Rd b/man/FOCUS_2006.Rd new file mode 100644 index 0000000..56bccac --- /dev/null +++ b/man/FOCUS_2006.Rd @@ -0,0 +1,31 @@ +\name{FOCUS_2006} +\alias{FOCUS_2006} +\docType{data} +\title{ + Example gmkin workspace for Datasets C and D from the FOCUS Kinetics report +} +\description{ + An \code{\link{gmkinws}} object with data taken from FOCUS (2006), Appendix + 3. This is the the workspace that is loaded into \code{\link{gmkin}} by + default. +} +\usage{FOCUS_2006} +\format{ + A list named \code{FOCUS_2006} containing the components + needed to populate the gmkin user interface. +} +\examples{ + \dontrun{ + save(FOCUS_2006, file = "FOCUS_2006.RData") + # Now you can load the file "FOCUS_2006.RData" from gmkin, + # restoring the workspace that is loaded at startup. + } +} +\source{ + FOCUS (2006) \dQuote{Guidance Document on Estimating Persistence and + Degradation Kinetics from Environmental Fate Studies on Pesticides in EU + Registration} Report of the FOCUS Work Group on Degradation Kinetics, + EC Document Reference Sanco/10058/2005 version 2.0, 434 pp, + \url{http://focus.jrc.ec.europa.eu/dk} +} +\keyword{datasets} diff --git a/man/FOCUS_2006_Z.Rd b/man/FOCUS_2006_Z.Rd new file mode 100644 index 0000000..ac7098c --- /dev/null +++ b/man/FOCUS_2006_Z.Rd @@ -0,0 +1,28 @@ +\name{FOCUS_2006_Z} +\alias{FOCUS_2006_Z} +\docType{data} +\title{ + Example gmkin workspace for Dataset Z from the FOCUS Kinetics report +} +\description{ + Data taken from FOCUS (2006), Appendix 7, p. 350. +} +\usage{FOCUS_2006_Z} +\format{ + An \code{\link{gmkinws}} object with dataset Z taken from FOCUS (2006), + together with most of the models used in the corresponding vignette. +} +\examples{ + \dontrun{ + save(FOCUS_2006_Z, file = "FOCUS_2006_Z.RData") + # Now you can load the file "FOCUS_2006_Z.RData" from gmkin + } +} +\source{ + FOCUS (2006) \dQuote{Guidance Document on Estimating Persistence and + Degradation Kinetics from Environmental Fate Studies on Pesticides in EU + Registration} Report of the FOCUS Work Group on Degradation Kinetics, + EC Document Reference Sanco/10058/2005 version 2.0, 434 pp, + \url{http://focus.jrc.ec.europa.eu/dk} +} +\keyword{datasets} diff --git a/man/FOCUS_2006_Z_gmkin.Rd b/man/FOCUS_2006_Z_gmkin.Rd deleted file mode 100644 index 44edded..0000000 --- a/man/FOCUS_2006_Z_gmkin.Rd +++ /dev/null @@ -1,28 +0,0 @@ -\name{FOCUS_2006_Z_gmkin} -\alias{FOCUS_2006_Z_gmkin} -\docType{data} -\title{ - Example gmkin workspace for Dataset Z from the FOCUS Kinetics report -} -\description{ - Data taken from FOCUS (2006), Appendix 7, p. 350. -} -\usage{FOCUS_2006_Z_gmkin} -\format{ - A list named \code{FOCUS_2006_Z_gmkin} containing the components - needed to populate the \code{\link{gmkin}} user interface. -} -\examples{ - \dontrun{ - save(FOCUS_2006_Z_gmkin, file = "FOCUS_2006_Z_gmkin.RData") - # Now you can load the file "FOCUS_2006_Z_gmkin.RData" from gmkin - } -} -\source{ - FOCUS (2006) \dQuote{Guidance Document on Estimating Persistence and - Degradation Kinetics from Environmental Fate Studies on Pesticides in EU - Registration} Report of the FOCUS Work Group on Degradation Kinetics, - EC Document Reference Sanco/10058/2005 version 2.0, 434 pp, - \url{http://focus.jrc.ec.europa.eu/dk} -} -\keyword{datasets} diff --git a/man/FOCUS_2006_gmkin.Rd b/man/FOCUS_2006_gmkin.Rd deleted file mode 100644 index df0a22a..0000000 --- a/man/FOCUS_2006_gmkin.Rd +++ /dev/null @@ -1,30 +0,0 @@ -\name{FOCUS_2006_gmkin} -\alias{FOCUS_2006_gmkin} -\docType{data} -\title{ - Example gmkin workspace for Datasets C and D from the FOCUS Kinetics report -} -\description{ - Data taken from FOCUS (2006), Appendix 3. This is the the workspace that is - loaded into \code{\link{gmkin}} by default. -} -\usage{FOCUS_2006_gmkin} -\format{ - A list named \code{FOCUS_2006_gmkin} containing the components - needed to populate the gmkin user interface. -} -\examples{ - \dontrun{ - save(FOCUS_2006_gmkin, file = "FOCUS_2006_gmkin.RData") - # Now you can load the file "FOCUS_2006_gmkin.RData" from gmkin, - # restoring the workspace that is loaded at startup. - } -} -\source{ - FOCUS (2006) \dQuote{Guidance Document on Estimating Persistence and - Degradation Kinetics from Environmental Fate Studies on Pesticides in EU - Registration} Report of the FOCUS Work Group on Degradation Kinetics, - EC Document Reference Sanco/10058/2005 version 2.0, 434 pp, - \url{http://focus.jrc.ec.europa.eu/dk} -} -\keyword{datasets} diff --git a/vignettes/gmkin_manual.Rmd b/vignettes/gmkin_manual.Rmd index dd1ae7f..7200b12 100644 --- a/vignettes/gmkin_manual.Rmd +++ b/vignettes/gmkin_manual.Rmd @@ -400,6 +400,6 @@ a fit has been run and confidence intervals were successfully calculated for the if the model was not overparameterised and no other problems occurred), the confidence intervals are graphically displayed as bars as shown below. -![conficence](img/confidence.png) +![confidence](img/confidence.png) diff --git a/vignettes/gmkin_manual.html b/vignettes/gmkin_manual.html index bff6a74..8ae6ef8 100644 --- a/vignettes/gmkin_manual.html +++ b/vignettes/gmkin_manual.html @@ -244,7 +244,7 @@ Model cost at call 37 : 371.2134

Confidence interval plots

Whenever a new fit has been configured or a run of a fit has been completed, the plotting area is updated with the abovementioned plot of the data and the current model solution.

In addition, a confidence interval plot is shown below this conventional plot. In case a fit has been run and confidence intervals were successfully calculated for the fit (i.e. if the model was not overparameterised and no other problems occurred), the confidence intervals are graphically displayed as bars as shown below.

-

conficence

+

confidence

diff --git a/vignettes/gmkin_manual.md b/vignettes/gmkin_manual.md new file mode 100644 index 0000000..bab6770 --- /dev/null +++ b/vignettes/gmkin_manual.md @@ -0,0 +1,408 @@ +--- +title: "Manual for gmkin" +output: + html_document: + css: gmkin_manual.css + toc: true + theme: united +--- + + + +## Introduction + +The R add-on package gmkin provides a browser based graphical interface for +performing kinetic evaluations of degradation data using the mkin package. +While the use of gmkin should be largely self-explanatory, this manual may serve +as a functionality overview and reference. + +For system requirements and installation instructions, please refer to the +[gmkin homepage](http://kinfit.r-forge.r-project.org/gmkin_static) + +## Starting gmkin + +As gmkin is an R package, you need to start R and load the gmkin package before you can run gmkin. +This can be achieved by entering the command + + +```r +library(gmkin) +``` + +into the R console. This will also load the packages that gmkin depends on, +most notably gWidgetsWWW2 and mkin. Loading the package only has to be done +once after you have started R. + +Before you start gmkin, you should make sure that R is using the working +directory that you would like to keep your gmkin project file(s) in. If you use +the standard R application on windows, you can change the working directory +from the File menu. + +Once you are sure that the working directory is what you want it to be, gmkin +can be started by entering the R command + + +```r +gmkin() +``` + +This will cause the default browser to start up or, if it is already running, to +pop up and open a new tab for displaying the gmkin user interface. + +In the R console, you should see some messages, telling you if the local R help +server, which also serves the gmkin application, has been started, which port it is +using and that it is starting an app called gmkin. + +Finally, it should give a message like + + +```r +Model cost at call 1: 2388.077 +``` + +which means that the first kinetic evaluation has been configured for fitting. + +In the browser, you should see something like the screenshot below. + +![gmkin start](img/gmkin_start.png) + +The statusbar at the bottom of the gmkin window shows, among others, the +working directory that gmkin uses. + +Note that the project file management area described below can be minimized by clicking on +the arrows on the right hand side of its title bar. This may be helpful if the vertical +size of your browser window is restricted. + +## Project file management + +At startup, gmkin loads a project called "FOCUS\_2006\_gmkin" which is distributed +with the gmkin package. A gmkin project contains datasets, kinetic models for +fitting, and so-called fits, i.e. the results of fitting models to data. These +gmkin projects can be saved and restored using the project file management area in the +top left. + +![projects](img/projects.png) + +If you would like to save these items for reference or for the purpose of continuing +your work at a later time, you can modify the project name and press the button below it. +The full name of the project file created and the working directory will be displayed +in the gmkin status bar. + +For restoring a previously saved project file, use the Browse button to locate +it, and the "Upload" button to load its contents into gmkin. + +## Studies + +The "Studies" area directly below the "Project file management" area can be expanded by clicking +on the arrows on the right hand side of its title bar. Studies in gmkin are +simply a numbered list of sources for the datasets in a project. You can edit the titles +directly by clicking on them. If you would like to add a new data source, use the "Add" +button above the table containing the list. If there are more than one studies in the list, +you can also remove them using the "Remove" button. + +![studies](img/studies.png) + +Note that the user is responsible to keep the study list consistent with the numbers that are +used in the list of datasets described below. + +## Datasets and Models +The project loaded at the start of gmkin contains two datasets and four kinetic models. These +are listed to the left under the heading "Datasets and Models", together with a button for +setting up fits as shown below. + +![datasets and models](img/datasetsnmodels.png) + +For editing, adding or removing datasets or models, you need to double-click on an +entry in the respective list. + +For setting up a fit of a specific model to a specific dataset, the model and +the dataset should be selected by clicking on them. If they are compatible, clicking +the button "Configure fit for selected dataset and model" will set up the fit and +open the "Plotting and Fitting" tab to the right. + +## Dataset editor + +The dataset editor allows for editing datasets, entering new datasets, uploading +data from text files and deleting datasets. + +![dataset editor](img/dataseteditor.png) + +If you want to create (enter or load) a new dataset, it is wise to first edit +the list of data sources in the "Studies" area as described above. + +### Entering data directly + +For entering new data manually, click on "New dataset", enter a title and select +the study from which the dataset is taken. At this stage, you may already want +to press "Keep changes", so the dataset appears in the list of datasets. + +In order to generate a table suitable for entering the data, enter a comma separated +list of sampling times, optionally the time unit, and the number of replicate measurements +at each sampling time. Also, add a comma separated list of short names of the +relevant compounds in your dataset. A unit can be specified for the observed +values. An example of filling out the respective fields is shown below. + +![generate data grid](img/generatedatagrid.png) + +Once everyting is filled out to your satisfaction, press the button "Generate empty grid +for kinetic data". In our example, this would result in the data grid shown below. You +can enter the observed data into the value column, as shown in the screenshot below. + +![data grid](img/datagrid.png) + +The column with title override serves to override data points from the original +datasets, without loosing the information which value was originally reported. + +If everything is OK, press "Keep changes" to save the dataset in the current +workspace. Note that you need to save the project file (see above) in order to +be able to use the dataset that you created in a future gmkin session. + +### Importing data from text files + +In case you want to work with a larger dataset that is already available as a computer +file e.g. in a spreadsheet application, you can export these data as a tab separated +or comma separated text file and import it using the "Browse" and "Upload" buttons in the +dataset editor. + +As an example, we can create a text file from one of the datasets shipped with +the mkin package using the following R command: + + +```r +write.table(schaefer07_complex_case, sep = ",", dec = ".", + row.names = FALSE, quote = FALSE, + file = "schaefer07.csv") +``` + +This produces a text file with comma separated values in the current working directory of R. + +Loading this text file into gmkin using the "Browse" and "Upload" buttons results in +an import configuration area like this, with the uploaded text file displayed to the left, +and the import options to the right. + +![upload area](img/uploadarea.png) + +In the import configuration area, the following options can be specified. In the field +"Comment lines", the number of lines in the beginning of the file that should be ignored +can be specified. + +The checkbox on the next line should be checked if the first line of the file contains +the column names, i.e. the names of the observed variables when the data are in wide format. + +As "Separator", whitespace, semicolon or comma can be chosen. If whitespace is selected, +files in which the values are separated by a fixed or varying number of whitespace characters +should be read in correctly. As the tabulator counts as a whitespace character, this is +also the option to choose for tabulator separated values. + +As the "Decimal" separator, comma "," or period "." can be selected. + +In the next line, it can be specified if the data are in wide or in long format. +If in wide format, the only option left to specify is the title of the column containing +the sampling times. If the data is in long format, the column headings specifying the +columns containing the observed variables (default is "name"), the sampling times +(default is "time"), the observed values (default is "value") and, if present in the data, +the relative errors (default is "err") can be adapted. The default settings appearing if +the long format is selected are shown below. + +![long](img/long.png) + +In our example we have data in the wide format, and after adapting the +"Separator" to a comma, we can press the button "Import using options specified +below", and the data should be imported. If successful, the data editor should +show the sampling times and the names of the observed variables, as well as the +imported data in a grid for further editing or specifying overrides. + +After editing the title of the dataset and selecting the correct study as +the source of the data, the dataset editor should look like shown below. + +![successful upload](img/successfulupload.png) + +If everything is OK, press "Keep changes" to save the dataset in the current +workspace. Again, you need to save the project file in order to be able to use +the dataset that you created in a future gmkin session. + +## Model editor + +The following screenshot shows the model editor for the model number 4 in +the list of models that are in the initial workspace. + +![model editor](img/modeleditor.png) + +In the first line the name of the model can be edited. You can also specify "min" or +"max" for minimum or maximum use of formation fractions. Maximum use of formation +fractions means that the differential equations in the degradation model are formulated +using formation fractions. When you specify "min", then formation fractions are only used +for the parent compound when you use the FOMC, DFOP or the HS model for it. + +Pressing "Copy model" keeps the model name, so you should change it for the newly generated copy. +Pressing "Add observed variable" adds a line in the array of state variable specifications below. +The observed variables to be added are usually transformation products (usually termed metabolites), +but can also be the parent compound in a different compartment (e.g. "parent\_sediment"). + +Only observed variable names that occur in previously defined datasets can be selected. For any observed +variable other than the first one, only the SFO or the SFORB model can be selected. For each +observed variables, a comma separated list of target variables can be specified. In addition, a pathway +to the sink compartment can be selected. If too many observed variables have been added, complete lines +can be removed from the model definition by pressing the button "Remove observed variable". + +If the model definition is supposedly correct, press "Keep changes" to make it possible to select +it for fitting in the listing of models to the left. + +## Plotting and fitting + +If the dataset(s) to be used in a project are created, and suitable kinetic models have been defined, +kinetic evaluations can be configured by selecting one dataset and one model in the lists to the left, +and the pressing the button "Configure fit for selected dataset and model" below these lists. + +This opens the "Plotting and fitting" tab area to the right, consisting of a graphical window +showing the data points in the selected dataset and the model, evaluated with the initial parameters +defined by calling `mkinfit` without defining starting parameters. The value of the objective function +to be minimized for these default parameters can be seen in the R console, e.g. as + + +```r +Model cost at call 1: 15156.12 +``` + +for the example shown below, where the FOCUS example dataset D and the model SFO\_SFO were selected. + +![plotting and fitting](img/plottingnfitting.png) + +### Parameters + +In the right hand area, initially the tab with the parameter list is displayed. While +name and type of the parameters should not be edited, their initial values can be edited +by clicking on a row. Also, it can be specified if the parameters should be fixed +in the optimisation process. + +If the initial values for the parameters were changed, the resulting model solution +can be visually checked by pressing the button "Show initial". This will update the +plot of the model and the data using the specified initial parameter values. + +If a similar model with a partially overlapping model definition has already be fitted, +initial values for parameters with the same name in both models can also be retrieved +from previous fits by selecting the fit and pressing the button "Get initials +from". This facilitates stepwise fitting of more complex degradation pathways. + +After the model has been successfully fitted by pressing the "Run" button, the optimised +parameter values are added to the parameter table. + +### Fit options + +The most important fit options of the `mkinfit` function can be set via the +"Fit option" tab shown below. If the "plot" checkbox is checked, an R graphics device +started via the R console shows the fitting progress, i.e. the change of the model +solution together with the data during the optimisation. + +![fit options](img/fitoptions.png) + +The "solution\_type" can either be "auto", which means that the most effective solution +method is chosen for the model, in the order of "analytical" (for parent only degradation +data), "eigen" (for differential equation models with only linear terms, i.e. without +FOMC, DFOP or HS submodels) or "deSolve", which can handle all model definitions generated +by the `mkin` package. + +The parameters "atol" and "rtol" are only effective if the solution type is "deSolve". They +control the precision of the iterative numerical solution of the differential equation model. + +The checkboxes "transform\_rates" and "transform\_fractions" control if the parameters are fitted +as defined in the model, or if they are internally transformed during the fitting process in +order to improve the estimation of standard errors and confidence intervals which are based +on a linear approximation at the optimum found by the fitting algorithm. + +If fitting with transformed fractions leads to a suboptimal fit, doing a first +run without transforming fractions may help. A final run using the optimised +parameters from the previous run as starting values (see comment on "Get +initials from" above) can then be performed with transformed fractions. + +The dropdown box "weight" specifies if and how the observed values should be weighted +in the fitting process. If "manual" is chosen, the values in the "err" column of the +dataset are used, which are set to unity by default. Setting these to higher values +gives lower weight and vice versa. If "none" is chosen, observed +values are not weighted. Please refer to the documentation of the `modFit` function from +the `FME` package for the meaning of options "std" and "mean". + +The options "reweight.method", "reweight.tol" and "reweight.max.iter" enable the use of +iteratively reweighted least squares fitting, if the reweighting method is set to "obs". Please +refer to the `mkinfit` [documentation](http://kinfit.r-forge.r-project.org/mkin_static/mkinfit.html) +for more details. + +The drop down box "method.modFit" makes it possible to choose between the optimisation +algorithms "Port" (the default in mkin versions > 0.9-33, a local optimisation +algorithm using a model/trust region approach), "Marq" (the former default in +mkin, a Levenberg-Marquardt variant from the R package `minpack.lm`), +and "SANN" (the simulated annealing method - robust but inefficient and without +a convergence criterion). + +Finally, the maximum number of iterations for the optimisation can be adapted using the +"maxit.modFit" field. + +### Fitting the model + +In many cases the starting parameters and the fit options do not need to be modified +and the model fitting process can simply be started by pressing the "Run" button. +In the R console, the progressive reduction in the model cost can be monitored and will +be displayed like this: + + +```r +Model cost at call 1 : 15156.12 +Model cost at call 3 : 15156.12 +Model cost at call 7 : 14220.79 +Model cost at call 8 : 14220.79 +Model cost at call 11 : 14220.79 +Model cost at call 12 : 3349.268 +Model cost at call 15 : 3349.268 +Model cost at call 17 : 788.6367 +Model cost at call 18 : 788.6366 +Model cost at call 22 : 374.0575 +Model cost at call 23 : 374.0575 +Model cost at call 27 : 371.2135 +Model cost at call 28 : 371.2135 +Model cost at call 32 : 371.2134 +Model cost at call 36 : 371.2134 +Model cost at call 37 : 371.2134 +``` + +If plotting of the fitting progress was selecte in the "Fit options" tab, a +new separate graphics window should either pop up, or a graphics window previously +started for this purpose will be reused. + +### Summary + +Once a fit has successfully been performed by pressing the "Run" button, the summary +as displayed below can be accessed via the "Summary" tab. + +![summary](img/summary.png) + +The complete summary can be saved into a text file by specifying a suitable file name +and pressing the button "Save summary". + +### Plot options + +In the tab "Plot options", the file format can be chosen, the legend can be +turned off, and the observed variables for which the data and the model fit +should be plotted can be selected as shown below. + +![plot options](img/plotoptions.png) + +On systems running the Windows operating system, the windows metafile (wmf) format +can be additionally chosen. Chaning the file format for plotting will also change +the extension of the proposed filename for saving the plot. + +### Confidence interval plots + +Whenever a new fit has been configured or a run of a fit has been completed, the plotting +area is updated with the abovementioned plot of the data and the current model solution. + +In addition, a confidence interval plot is shown below this conventional plot. In case +a fit has been run and confidence intervals were successfully calculated for the fit (i.e. +if the model was not overparameterised and no other problems occurred), the +confidence intervals are graphically displayed as bars as shown below. + +![confidence](img/confidence.png) + + -- cgit v1.2.1