aboutsummaryrefslogtreecommitdiff
path: root/R
diff options
context:
space:
mode:
authorjranke <jranke@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>2012-06-28 04:59:12 +0000
committerjranke <jranke@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>2012-06-28 04:59:12 +0000
commit448fd5ede69121c9f4c693ed72ade98d6b9b83e0 (patch)
tree04f09ae5f60208e661631db352b1c42d8b34f396 /R
parentac2bb47b1f5f147b8b6a716b42d46b46a7adc60b (diff)
- Formatting improvement of mkinmod
- Small fix in mkinplot git-svn-id: svn+ssh://svn.r-forge.r-project.org/svnroot/kinfit/pkg/mkin@45 edb9625f-4e0d-4859-8d74-9fd3b1da38cb
Diffstat (limited to 'R')
-rw-r--r--R/mkinmod.R29
-rw-r--r--R/mkinplot.R8
2 files changed, 19 insertions, 18 deletions
diff --git a/R/mkinmod.R b/R/mkinmod.R
index c7f11d9..1a1c55c 100644
--- a/R/mkinmod.R
+++ b/R/mkinmod.R
@@ -1,6 +1,6 @@
# $Id$
-# Copyright (C) 2010-2012 Johannes Ranke#{{{
+# Copyright (C) 2010-2012 Johannes Ranke {{{
# Contact: jranke@uni-bremen.de
# This file is part of the R package mkin
@@ -16,7 +16,7 @@
# details.
# You should have received a copy of the GNU General Public License along with
-# this program. If not, see <http://www.gnu.org/licenses/>#}}}
+# this program. If not, see <http://www.gnu.org/licenses/> }}}
mkinmod <- function(..., use_of_ff = "min")
{
@@ -47,11 +47,11 @@ mkinmod <- function(..., use_of_ff = "min")
} else message <- "ok"
} else mat = TRUE#}}}
- # Establish list of differential equations as well as map from observed#{{{
+ # Establish list of differential equations as well as map from observed {{{
# compartments to differential equations
for (varname in obs_vars)
{
- # Check the type component of the compartment specification#{{{
+ # Check the type component of the compartment specification {{{
if(is.null(spec[[varname]]$type)) stop(
"Every part of the model specification must be a list containing a type component")
if(!spec[[varname]]$type %in% c("SFO", "FOMC", "DFOP", "HS", "SFORB")) stop(
@@ -59,8 +59,8 @@ mkinmod <- function(..., use_of_ff = "min")
if(spec[[varname]]$type %in% c("FOMC", "DFOP", "HS") & match(varname, obs_vars) != 1) {
stop(paste("Types FOMC, DFOP and HS are only implemented for the first compartment,",
"which is assumed to be the source compartment"))
- }#}}}
- # New (sub)compartments (boxes) needed for the model type#{{{
+ } #}}}
+ # New (sub)compartments (boxes) needed for the model type {{{
new_boxes <- switch(spec[[varname]]$type,
SFO = varname,
FOMC = varname,
@@ -69,22 +69,23 @@ mkinmod <- function(..., use_of_ff = "min")
SFORB = paste(varname, c("free", "bound"), sep="_")
)
map[[varname]] <- new_boxes
- names(map[[varname]]) <- rep(spec[[varname]]$type, length(new_boxes))#}}}
- # Start a new differential equation for each new box#{{{
+ names(map[[varname]]) <- rep(spec[[varname]]$type, length(new_boxes)) #}}}
+ # Start a new differential equation for each new box {{{
new_diffs <- paste("d_", new_boxes, " =", sep="")
names(new_diffs) <- new_boxes
- diffs <- c(diffs, new_diffs)#}}}
- }#}}}
+ diffs <- c(diffs, new_diffs) #}}}
+ } #}}}
- # Create content of differential equations and build parameter list#{{{
+ # Create content of differential equations and build parameter list {{{
for (varname in obs_vars)
{
# Get the name of the box(es) we are working on for the decline term(s)
box_1 = map[[varname]][[1]] # This is the only box unless type is SFORB
if(spec[[varname]]$type %in% c("SFO", "SFORB")) { # {{{ Add SFO or SFORB decline term
if (use_of_ff == "min") { # Minimum use of formation fractions
- # Turn on sink if this is not explicitly excluded by the user by specifying sink=FALSE
- if(is.null(spec[[varname]]$sink)) spec[[varname]]$sink <- TRUE
+ # Turn on sink if this is not explicitly excluded by the user by
+ # specifying sink=FALSE
+ if(is.null(spec[[varname]]$sink)) spec[[varname]]$sink <- TRUE
if(spec[[varname]]$sink) {
# If sink is required, add first-order sink term
@@ -170,7 +171,7 @@ mkinmod <- function(..., use_of_ff = "min")
}
}
} #}}}
- }#}}}
+ } #}}}
model <- list(diffs = diffs, parms = parms, map = map, use_of_ff = use_of_ff)
diff --git a/R/mkinplot.R b/R/mkinplot.R
index 789a6f9..7641d26 100644
--- a/R/mkinplot.R
+++ b/R/mkinplot.R
@@ -24,15 +24,15 @@ mkinplot <- function(fit, xlab = "Time", ylab = "Observed", xlim = range(fit$dat
plot(0, type="n",
xlim = xlim, ylim = ylim,
xlab = xlab, ylab = ylab, ...)
- col_obs <- pch_obs <- 1:length(fit$mkinmod$map)
- names(col_obs) <- names(pch_obs) <- names(fit$mkinmod$map)
+ col_obs <- pch_obs <- lty_obs <- 1:length(fit$mkinmod$map)
+ names(col_obs) <- names(pch_obs) <- names(lty_obs) <- names(fit$mkinmod$map)
for (obs_var in names(fit$mkinmod$map)) {
points(subset(fit$data, variable == obs_var, c(time, observed)),
- pch = pch_obs[obs_var], col = col_obs[obs_var])
+ pch = pch_obs[obs_var], col = col_obs[obs_var])
}
matlines(out$time, out[-1])
if (legend == TRUE) {
legend("topright", inset=c(0.05, 0.05), legend=names(fit$mkinmod$map),
- col=col_obs, pch=pch_obs, lty=1:length(pch_obs))
+ col=col_obs, pch=pch_obs, lty=lty_obs)
}
}

Contact - Imprint