Skip to content
Snippets Groups Projects
Commit 9a84e517 authored by Claus Jonathan Fritzemeier's avatar Claus Jonathan Fritzemeier
Browse files

changes to modelorg for version 2.0

parent 39b1f500
No related branches found
No related tags found
No related merge requests found
......@@ -54,9 +54,7 @@ addReact <- function(model,
stop("needs an object of class modelorg!")
}
if(!.hasSlot(model, "version")){
validObject(model)
}
stopifnot(checkVersion(model))
if (length(met) != length(Scoef)) {
stop("arguments 'met' and 'Scoef' must have the same length")
......
......@@ -41,9 +41,7 @@ geneDel <- function(model, genes, checkId = FALSE) {
stop("needs an object of class modelorg!")
}
if(!.hasSlot(model, "version")){
validObject(model)
}
stopifnot(checkVersion(model))
if (isTRUE(checkId)) {
if (is(genes, "character")) {
......@@ -99,9 +97,10 @@ geneDel <- function(model, genes, checkId = FALSE) {
#print(reactInd)
#x <- logical(length(allGenes(model)))
x <- rep(TRUE, length(allGenes(model)))
xAll <- rep(TRUE, length(allGenes(model)))
#print(x)
x[geneInd] <- FALSE
xAll[geneInd] <- FALSE
names(xAll) <- allGenes(model)
constReact <- logical(length(reactInd))
#print(constReact)
......@@ -112,10 +111,15 @@ geneDel <- function(model, genes, checkId = FALSE) {
# If that's the case, the reaction needs gene bla.
ru <- gprRules(model)[reactInd]
ge <- genes(model)[reactInd]
for(i in 1:length(reactInd)) {
#print(reactInd[i])
#print(ru[i])
#ev <- eval(parse(text = ru[i]))
#define x for eval:
x <- xAll[ge[[i]]]
ev <- tryCatch(eval(parse(text = ru[i])), error = function(e) e)
if (is(ev, "simpleError")) {
stop("wrong gene association:",
......
......@@ -604,6 +604,7 @@ setMethod("optimizeProb", signature(object = "modelorg"),
prCmd = NA, poCmd = NA,
prCil = NA, poCil = NA, ...) {
stopifnot(checkVersion(object))
if (!is.null(gene)) {
if (!is.null(react)) {
......@@ -1097,13 +1098,13 @@ setMethod("singletonMetabolites", signature(object = "modelorg"),
setMethod("checkVersion", signature(object = "modelorg"),
function(object) {
if(!.hasSlot(object, "version")){
stop("No version slot found. Please use upgradeModelorg on object")
return("No version slot found. Please use upgradeModelorg with object")
}
if(compareVersion(version(object), SYBIL_SETTINGS("MODELORG_VERSION")) == 0){
return(TRUE)
}
stop(paste0("modelorg has version ", object(version), ", but you need at least version ", version))
return(paste0("modelorg has version ", version(object), ", but you need at least version ", version))
}
)
......
......@@ -42,9 +42,7 @@ rmReact <- function(model, react, rm_met = TRUE) {
stop("needs an object of class modelorg!")
}
if(!.hasSlot(model, "version")){
validObject(model)
}
stopifnot(checkVersion(model))
# check this, propably working wrong
if (is.na(match(is(react)[1], c("reactId", "numeric", "integer", "character")))) {
......
......@@ -38,13 +38,10 @@
return("needs an object of class modelorg!")
}
if(compareVersion(version(object), SYBIL_SETTINGS("MODELORG_VERSION")) != 0){
if(compareVersion(version(object), SYBIL_SETTINGS("MODELORG_VERSION")) == -1){
return("You are using an old version of the modelorg-Class. Use upgradeModelorg to get a compatible object!")
}
if(compareVersion(version(object), SYBIL_SETTINGS("MODELORG_VERSION")) == 1){
return("You are using a new version of the modelorg-Class. Plase upgrade your sybil package!")
}
versionCheck <- checkVersion(object)
if(!isTRUE(versionCheck)){
return(versionCheck)
}
if ((length(mod_id(object)) != 1) || (length(mod_name(object)) != 1)) {
......
No preview for this file type
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment