Skip to content

Commit

Permalink
version 0.7-1
Browse files Browse the repository at this point in the history
  • Loading branch information
tpetzoldt authored and gaborcsardi committed Dec 1, 2010
1 parent a184a5e commit 0337e7c
Show file tree
Hide file tree
Showing 15 changed files with 49 additions and 254 deletions.
6 changes: 3 additions & 3 deletions DESCRIPTION
@@ -1,5 +1,5 @@
Package: simecol
Version: 0.7
Version: 0.7-1
Date: 2010-12-01
Title: Simulation of ecological (and other) dynamic systems
Author: Thomas Petzoldt
Expand All @@ -15,6 +15,6 @@ Description: simecol is an object oriented framework to simulate
of code.
License: GPL (>= 2)
URL: http://www.simecol.de/
Packaged: 2010-11-30 09:44:02 UTC; thpe
Packaged: 2011-03-20 19:30:01 UTC; petzoldt
Repository: CRAN
Date/Publication: 2010-11-30 10:14:02
Date/Publication: 2011-03-21 06:47:44
13 changes: 0 additions & 13 deletions DESCRIPTION.$$$

This file was deleted.

1 change: 0 additions & 1 deletion R/addtoenv.R
@@ -1,7 +1,6 @@
## environment manipulation function
## Warning: use carefully and avoid name mangling
## solution provided by Gabor Grothendieck (replaces older own function)
## --> this function is deprecated and may be removed in further versions

addtoenv <- function(L, p = parent.frame()) {
for(nm in names(L)) {
Expand Down
24 changes: 12 additions & 12 deletions R/sEdit.R
Expand Up @@ -49,7 +49,7 @@ sEdit <- function(x, title="Please enter values:") {
row.names <- paste("var",1:length(slot),sep="")
}
for (i in 1:length(slot)) {
entries[[i]] <- tkentry(tt, textvariable=row.names[i])
entries[[i]] <- tkentry(tt, textvariable=row.names[i])
tkgrid(tklabel(tt,text=row.names[i]), entries[[i]])
}
reset.but <- tkbutton(tt, text="Reset", command=reset)
Expand Down Expand Up @@ -82,7 +82,7 @@ sEdit <- function(x, title="Please enter values:") {
ret <- lapply(ret, listToNum)
} else {
## default editor, e.g. data.frame or if tcltk is missing
ret <- edit(x)
ret <- edit(x)
}
return(ret)
}
Expand All @@ -97,9 +97,9 @@ setMethod("fixParms", "simObj",
function(x) {
sl <- "parms"
subx <- substitute(x)
if (is.name(subx))
if (is.name(subx))
subx <- deparse(subx)
if (!is.character(subx) || length(subx) != 1)
if (!is.character(subx) || length(subx) != 1)
stop("this function requires a name")
if (!(sl %in% slotNames(x)))
stop(paste("'", sl, "' does not exist in ", subx, sep=""))
Expand All @@ -108,17 +108,17 @@ setMethod("fixParms", "simObj",
slot(x, sl) <- ret
## interactive function is assumed to work
## in global environment
assign(subx, x, env=.GlobalEnv)
assign(subx, x, envir=.GlobalEnv)
}
)

setMethod("fixTimes", "simObj",
function(x) {
sl <- "times"
subx <- substitute(x)
if (is.name(subx))
if (is.name(subx))
subx <- deparse(subx)
if (!is.character(subx) || length(subx) != 1)
if (!is.character(subx) || length(subx) != 1)
stop("this function requires a name")
if (!(sl %in% slotNames(x)))
stop(paste("'", sl, "' does not exist in ", subx, sep=""))
Expand All @@ -131,7 +131,7 @@ setMethod("fixTimes", "simObj",
slot(x, sl) <- ret
## interactive function is assumed to work
## in global environment
assign(subx, x, env=.GlobalEnv)
assign(subx, x, envir=.GlobalEnv)

}
)
Expand All @@ -140,9 +140,9 @@ setMethod("fixInit", "simObj",
function(x) {
sl <- "init"
subx <- substitute(x)
if (is.name(subx))
if (is.name(subx))
subx <- deparse(subx)
if (!is.character(subx) || length(subx) != 1)
if (!is.character(subx) || length(subx) != 1)
stop("this function requires a name")
if (!(sl %in% slotNames(x)))
stop(paste("'", sl, "' does not exist in ", subx, sep=""))
Expand All @@ -151,11 +151,11 @@ setMethod("fixInit", "simObj",
slot(x, sl) <- ret
## interactive function is assumed to work
## in global environment
assign(subx, x, env=.GlobalEnv)
assign(subx, x, envir=.GlobalEnv)

}
)




Binary file modified data/chemostat.rda
Binary file not shown.
2 changes: 1 addition & 1 deletion demo/00Index
@@ -1,2 +1,2 @@
jss Sourcecode and demo for Petzoldt and Rinke (2007): Journal of Statistical Software, vol. 22 issue 09
rwalk3d Demo of a random walk model in 3D

181 changes: 0 additions & 181 deletions demo/rwalk3d.R

This file was deleted.

3 changes: 3 additions & 0 deletions inst/NEWS
@@ -1,3 +1,6 @@
0.7-1
o fix documentation notes and a warning

0.7
o "inputs" is now passed explicitly to sim "odeModel"
o fix namespace issue
Expand Down
Binary file modified inst/doc/a-simecol-introduction.pdf
Binary file not shown.
Binary file modified inst/doc/b-simecol-howtos.pdf
Binary file not shown.
Binary file modified inst/doc/ca.pdf
Binary file not shown.
43 changes: 18 additions & 25 deletions inst/doc/examples/chemostat.R
@@ -1,27 +1,20 @@
chemostat <- new("odeModel",
main = function(time, init, parms, inputs=NULL) {
vm <- parms["vm"] # max growth rate
km <- parms["km"] # half saturation constant
D <- parms["D"] # dilution rate
S0 <- parms["S0"] # substrate in inflow
Y <- parms["Y"] # yield coefficient for substrate
X <- init[1] # cells (e.g. algae)
S <- init[2] # substrate (e.g. phosphorus)

mu <- vm * S/(km + S) # Monod equation
dx1 <- mu * X - D * X # cells
dx2 <- D *(S0 - S) - 1/Y * mu * X # substrate
list(c(dx1, dx2))
},
parms = c(
vm = 1.0, # 1/d
km = 2.0, # mumol Substrate/l
Y = 100, # cells /mumol Substrate
D = 0.5, # 1/d
S0 = 10 # mumol Substrate/l
),
times = c(from=0, to=40, by=.5),
init = c(X=10, S=10), # cells/l; umol Substrate/l
solver = "lsoda"
main = function(time, init, parms, inputs = NULL) {
with(as.list(c(init, parms)), {
mu <- vm * S / (km + S) # Monod equation
dx1 <- mu * X - D * X # cells, e.g. algae
dx2 <- D *(S0 - S) - 1/Y * mu * X # substrate, e.g. phosphorus
list(c(dx1, dx2))
})
},
parms = c(
vm = 1.0, # max growth rate, 1/d
km = 2.0, # half saturation constant, mumol / L
Y = 100, # cells /mumol Substrate
D = 0.5, # dilution rate, 1/d
S0 = 10 # substrate in inflow, mumol / L
),
times = c(from = 0, to = 40, by = .5),
init = c(X = 10, S = 10), # cells / L; Substrate umol / L
solver = "lsoda"
)

Binary file modified inst/doc/statespace.pdf
Binary file not shown.

0 comments on commit 0337e7c

Please sign in to comment.