diff --git a/NAMESPACE b/NAMESPACE index 737bebc00403fc8df1f2fa6bd54bc8212dd43a82..e782ef4835465a07be574fe5c2c7610ae3cb85da 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -7,6 +7,7 @@ import(lattice) importFrom("grDevices", "colorRampPalette", "grey") importFrom("graphics", "arrows", "hist", "points", "polygon", "segments") importFrom("utils", "combn", "edit", "read.table", "str", "write.table") +importFrom("utils", "compareVersion") exportPattern("^[^\\.]") diff --git a/R/addReact.R b/R/addReact.R index 101842d1dd21afc70518a1f98eaec010bce4a061..35e6a252a998e9d3147ebc08b7916fbdc6b9b35d 100644 --- a/R/addReact.R +++ b/R/addReact.R @@ -53,6 +53,8 @@ addReact <- function(model, if (!is(model, "modelorg")) { stop("needs an object of class modelorg!") } + + stopifnot(checkVersion(model)) if (length(met) != length(Scoef)) { stop("arguments 'met' and 'Scoef' must have the same length") @@ -137,6 +139,11 @@ addReact <- function(model, newsubSys <- subSys(model) newS <- S(model) + + newMetAttr <- met_attr(model) + newReactAttr <- react_attr(model) + newCompAttr <- comp_attr(model) + newModAttr <- mod_attr(model) if (isTRUE(addRow)) { @@ -179,6 +186,11 @@ addReact <- function(model, nrow = nNewRows, ncol = react_num(model)) newS <- Matrix::rBind(newS, newRows) + + # new met attrs + if(ncol(newMetAttr) > 0){ + newMetAttr[nrow(newMetAttr)+1:nNewRows, ] <- NA + } } if (isTRUE(addCol)) { # we add at most one column @@ -209,6 +221,12 @@ addReact <- function(model, # new column in stoichiometric matrix newS <- cBind(newS, rep(0, nrow(newS))) + # new react Attr + # only one new row, /bc we can only add one reaction a time. + if(ncol(newReactAttr) > 0){ + newReactAttr[nrow(newReactAttr)+1, ] <- NA + } + # subsystems if (any(is.na(subSystem))) { ss <- subSys(model) @@ -290,13 +308,14 @@ addReact <- function(model, # genes per reaction newgenes <- append(genes(model), list(gene_rule$gene)) newrule <- gene_rule$rule - - for (j in 1 : length(geneInd)) { - pat <- paste("x(", j, ")", sep = "") - repl <- paste("x[", geneInd[j], "]", sep = "") - - newrule <- gsub(pat, repl, newrule, fixed = TRUE) - } + + # not needed for modelorg version 2.0 +# for (j in 1 : length(geneInd)) { +# pat <- paste("x(", j, ")", sep = "") +# repl <- paste("x[", geneInd[j], "]", sep = "") +# +# newrule <- gsub(pat, repl, newrule, fixed = TRUE) +# } newgprRules <- append(gprRules(model), newrule) } @@ -356,6 +375,12 @@ addReact <- function(model, subSys(mod_out) <- newsubSys S(mod_out) <- newS + + react_attr(mod_out) <- newReactAttr + met_attr(mod_out) <- newMetAttr + comp_attr(mod_out) <- newCompAttr + mod_attr(mod_out) <- newModAttr + } else { diff --git a/R/geneDel.R b/R/geneDel.R index f69dad53e2d81e30d72d10da1367826db1fb6eaf..87811bb55e0474f12665dc6065d0a39c11a10845 100644 --- a/R/geneDel.R +++ b/R/geneDel.R @@ -41,6 +41,8 @@ geneDel <- function(model, genes, checkId = FALSE) { stop("needs an object of class modelorg!") } + stopifnot(checkVersion(model)) + if (isTRUE(checkId)) { if (is(genes, "character")) { # Check if all genes are there @@ -95,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) @@ -108,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:", diff --git a/R/generics.R b/R/generics.R index e249177a90f6bd4c028d15b46d8cf90591daf192..af64b93398d579728264339f40fbcd40d648d6bd 100644 --- a/R/generics.R +++ b/R/generics.R @@ -126,6 +126,10 @@ setGeneric(name = "checkStat", def = function(opt) { standardGeneric("checkStat") } ) +setGeneric(name = "checkVersion", + def = function(object, ...) { standardGeneric("checkVersion") } +) + setGeneric(name = "chlb", def = function(object) { standardGeneric("chlb") } ) @@ -147,6 +151,13 @@ setGeneric(name = "cmd<-", def = function(object, value) { standardGeneric("cmd<-") } ) +setGeneric(name = "comp_attr", + def = function(object) { standardGeneric("comp_attr") } +) +setGeneric(name = "comp_attr<-", + def = function(object, value) { standardGeneric("comp_attr<-") } +) + setGeneric(name = "ctrlfl", def = function(object) { standardGeneric("ctrlfl") } ) @@ -536,6 +547,13 @@ setGeneric(name = "maxSol", def = function(object, ...) { standardGeneric("maxSol") } ) +setGeneric(name = "met_attr", + def = function(object) { standardGeneric("met_attr") } +) +setGeneric(name = "met_attr<-", + def = function(object, value) { standardGeneric("met_attr<-") } +) + setGeneric(name = "met_comp", def = function(object) { standardGeneric("met_comp") } ) @@ -596,6 +614,13 @@ setGeneric(name = "minSol", def = function(object, ...) { standardGeneric("minSol") } ) +setGeneric(name = "mod_attr", + def = function(object) { standardGeneric("mod_attr") } +) +setGeneric(name = "mod_attr<-", + def = function(object, value) { standardGeneric("mod_attr<-") } +) + setGeneric(name = "mod_compart", def = function(object) { standardGeneric("mod_compart") } ) @@ -759,6 +784,13 @@ setGeneric(name = "react<-", def = function(object, value) { standardGeneric("react<-") } ) +setGeneric(name = "react_attr", + def = function(object) { standardGeneric("react_attr") } +) +setGeneric(name = "react_attr<-", + def = function(object, value) { standardGeneric("react_attr<-") } +) + setGeneric(name = "react_de", def = function(object) { standardGeneric("react_de") } ) @@ -945,6 +977,13 @@ setGeneric(name = "verblevel<-", def = function(object, value) { standardGeneric("verblevel<-") } ) +setGeneric(name = "version", + def = function(object) { standardGeneric("version") } +) +setGeneric(name = "version<-", + def = function(object, value) { standardGeneric("version<-") } +) + setGeneric(name = "writeProb", def = function(lp, fname, ff = "lp", ...) { standardGeneric("writeProb") } ) diff --git a/R/mod2irrev.R b/R/mod2irrev.R index 0d63548ea770aac241023adae18bac0b8a0fb997..658b10a26d9cf460c4634ce8b494caab90e85ca0 100644 --- a/R/mod2irrev.R +++ b/R/mod2irrev.R @@ -245,7 +245,7 @@ mod2irrev <- function(model, exex = FALSE) { allGenes(modelIr) <- allGenes(model) rxnG_temp <- rxnGeneMat(model) - rxnG_temp <- rxnG_temp[irrev2rev(modelIr),] + rxnG_temp <- rxnG_temp[irrev2rev(modelIr), ,drop=FALSE] #rxnG_temp <- rxnG_temp[irrev2rev,] rxnGeneMat(modelIr) <- rxnG_temp diff --git a/R/modelorgClass.R b/R/modelorgClass.R index 9f8702a5f2d758b418d0111498ec3af373625243..5cd4063e5cd24ab01b9f406e35558bea526576d4 100644 --- a/R/modelorgClass.R +++ b/R/modelorgClass.R @@ -39,22 +39,27 @@ setClass("modelorg", mod_id = "character", # model id mod_key = "character", # model key (unique character string) mod_compart = "character", # vector compartments + mod_attr = "data.frame", # dataframe to store attributes of the model + comp_attr = "data.frame", # dataframe to store attributes of the compartments met_num = "integer", # number of metabolites met_id = "character", # vector metabolite id's met_name = "character", # vector metabolite names met_comp = "integer", # vector the metabolites compartment met_single = "logical", # metabolites appearing only once in S met_de = "logical", # dead end metabolites + met_attr = "data.frame", # dataframe to store attributes of the metabolites react_num = "integer", # number of reactions react_rev = "logical", # vector reversibilities react_id = "character", # vector reaction id's react_name = "character", # vector reaction names react_single = "logical", # reactions using metabolites appearing only once in S react_de = "logical", # reactions using dead end metabolites + react_attr = "data.frame", # dataframe to store attributes of the reactions S = "Matrix", # matrix S lowbnd = "numeric", # vector reactions lower bounds uppbnd = "numeric", # vector reactions upper bounds obj_coef = "numeric", # vector objective coefficients + version = "character", # version to be compatible with changes in the class gprRules = "character", genes = "list", gpr = "character", @@ -110,9 +115,14 @@ setMethod(f = "initialize", .Object@mod_key <- as.character(.generateModKey()) .Object@react_num <- as.integer(0) .Object@met_num <- as.integer(0) + .Object@react_attr <- data.frame() + .Object@met_attr <- data.frame() + .Object@mod_attr <- data.frame() + .Object@comp_attr <- data.frame() .Object@S <- Matrix::Matrix(0, 0, 0) .Object@rxnGeneMat <- Matrix::Matrix(0, 0, 0) .Object@subSys <- Matrix::Matrix(0, 0, length(subSys)) + .Object@version <- SYBIL_SETTINGS("MODELORG_VERSION") if (!is.null(subSys)) { colnames(.Object@subSys) <- as.character(subSys) } @@ -204,7 +214,6 @@ setReplaceMethod("mod_compart", signature(object = "modelorg"), } ) - # number of metabolites setMethod("met_num", signature(object = "modelorg"), function(object) { @@ -548,6 +557,79 @@ setReplaceMethod("subSys", signature(object = "modelorg"), } ) +# reaction sub systems +setMethod("version", signature(object = "modelorg"), + function(object) { + return(object@version) + } +) + +setReplaceMethod("version", signature(object = "modelorg"), + function(object, value) { + object@version <- value + stopifnot(validObject(object)) + return(object) + } +) + +# metabolites attributes +setMethod("met_attr", signature(object = "modelorg"), + function(object) { + return(object@met_attr) + } +) + +setReplaceMethod("met_attr", signature(object = "modelorg"), + function(object, value) { + object@met_attr <- value + return(object) + } +) + +# reaction attributes +setMethod("react_attr", signature(object = "modelorg"), + function(object) { + return(object@react_attr) + } +) + +setReplaceMethod("react_attr", signature(object = "modelorg"), + function(object, value) { + object@react_attr <- value + return(object) + } +) + +# compartment attributes +setMethod("comp_attr", signature(object = "modelorg"), + function(object) { + return(object@comp_attr) + } +) + +setReplaceMethod("comp_attr", signature(object = "modelorg"), + function(object, value) { + object@comp_attr <- value + return(object) + } +) + +# model attributes +setMethod("mod_attr", signature(object = "modelorg"), + function(object) { + return(object@mod_attr) + } +) + +setReplaceMethod("mod_attr", signature(object = "modelorg"), + function(object, value) { + object@mod_attr <- value + return(object) + } +) + + + #------------------------------------------------------------------------------# # other methods # @@ -587,6 +669,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)) { @@ -1073,11 +1156,22 @@ setMethod("singletonMetabolites", signature(object = "modelorg"), } ) +#------------------------------------------------------------------------------# - - +setMethod("checkVersion", signature(object = "modelorg"), + function(object) { + if(!.hasSlot(object, "version")){ + return("No version slot found. Please use upgradeModelorg with object") + } + + if(compareVersion(version(object), SYBIL_SETTINGS("MODELORG_VERSION")) == 0){ + return(TRUE) + } + return(paste0("modelorg has version ", version(object), ", but you need at least version ", version)) + } +) diff --git a/R/parseBoolean.R b/R/parseBoolean.R index 653aecc2e37b9de4f45c91a9fc7737693cdc3eb8..4546b26b778bcd49ff2c08ff4d31cb58a54af7bd 100644 --- a/R/parseBoolean.R +++ b/R/parseBoolean.R @@ -31,6 +31,7 @@ # The algorithm is the same. # # 2015-06-17 CJF: added handling for emtpy gprRule like "( )" +# 2016-05-18 CJF: format of gprRules was changed. .parseBoolean <- function(gprRule, tokens = "()&|~") { @@ -88,7 +89,7 @@ gene_uniq <- unique(genes) newTok <- match(genes, gene_uniq) - newTok <- sapply(newTok, function(x) paste("x(", x, ")", sep = "")) + newTok <- sapply(newTok, function(x) paste("x[", x, "]", sep = "")) # rule <- diff --git a/R/readTEXTmod.R b/R/readTEXTmod.R index 8746664f786c00533e700bddd0dd2369addfb059..00e71cc53f663309af0f43c89334aa1032b263d0 100644 --- a/R/readTEXTmod.R +++ b/R/readTEXTmod.R @@ -24,9 +24,9 @@ ################################################ # Function: readTEXTmod -# -# # +# 2016-05-18 CJF: format of gprRules was changed. + readTEXTmod <- function(filename, description, @@ -112,7 +112,10 @@ parse_genes <- function(gene) { } # for the gpr slot and gprRules slot - gene_pos <- which(allGenes %in% gene) + #gene_pos <- which(allGenes %in% gene) + #new gprRules: + gene_pos <- seq(along=gene) + if (length(gene) > 1) { gpr_string <- paste("(", paste(gene, sep = "", collapse = " and "), ")") rules_string <- paste("x[", gene_pos, "]", sep = "") diff --git a/R/readTSVmod.R b/R/readTSVmod.R index f66c1bda4435b43d10a4b502b9f47db00ae40b81..032e82fd6b5af3e7cb00c652ab8de4cba175114d 100644 --- a/R/readTSVmod.R +++ b/R/readTSVmod.R @@ -26,7 +26,7 @@ # Function: readTSVmod # # -# +# 2016-05-18 CJF: format of gprRules was changed. readTSVmod <- function(prefix, suffix, reactList, metList = NA, modDesc = NA, @@ -949,13 +949,14 @@ readTSVmod <- function(prefix, suffix, if (isTRUE(RruleL[i])) { geneInd <- match(Rgenes[[i]], allGenes) rxnGeneMat[i, geneInd] <- TRUE + + # not needed for version 2.0 modelorg gprRules +# for (j in 1 : length(geneInd)) { +# pat <- paste("x(", j, ")", sep = "") +# repl <- paste("x[", geneInd[j], "]", sep = "") - for (j in 1 : length(geneInd)) { - pat <- paste("x(", j, ")", sep = "") - repl <- paste("x[", geneInd[j], "]", sep = "") - - Rrules[i] <- gsub(pat, repl, Rrules[i], fixed = TRUE) - } +# Rrules[i] <- gsub(pat, repl, Rrules[i], fixed = TRUE) +# } } } diff --git a/R/rmReact.R b/R/rmReact.R index 9b30a44388c8af1c7788484aa72fc8ea773e845e..c420d70941bb3161316ccfcf208bf212cbbf25f3 100644 --- a/R/rmReact.R +++ b/R/rmReact.R @@ -38,30 +38,31 @@ rmReact <- function(model, react, rm_met = TRUE) { # check model and react # #------------------------------------------------------------------------------# - if (!is(model, "modelorg")) { - stop("needs an object of class modelorg!") - } - - - # check this, propably working wrong - if (is.na(match(is(react)[1], c("reactId", "numeric", "integer", "character")))) { - stop("argument react must be numeric, character, or of class reactId. Use checkReactId!") - } - - # argument react comes from the function checkReactId() - if (is(react, "reactId")) { - rmReact <- react_pos(react) - } - else { - checked_react <- checkReactId(model, react) - #print(is(checked_react)) - if (!is(checked_react, "reactId")) { - stop("Check your reaction Id's") - } - else { - rmReact <- react_pos(checked_react) - } - } + if (!is(model, "modelorg")) { + stop("needs an object of class modelorg!") + } + + stopifnot(checkVersion(model)) + + # check this, propably working wrong + if (is.na(match(is(react)[1], c("reactId", "numeric", "integer", "character")))) { + stop("argument react must be numeric, character, or of class reactId. Use checkReactId!") + } + + # argument react comes from the function checkReactId() + if (is(react, "reactId")) { + rmReact <- react_pos(react) + } + else { + checked_react <- checkReactId(model, react) + #print(is(checked_react)) + if (!is(checked_react, "reactId")) { + stop("Check your reaction Id's") + } + else { + rmReact <- react_pos(checked_react) + } + } # if ((is(react, "numeric")) || (is(react, "integer"))) { @@ -132,6 +133,10 @@ rmReact <- function(model, react, rm_met = TRUE) { obj_coef(mod_out) <- obj_coef(model)[keepReact] react_single(mod_out) <- react_single(model)[keepReact] react_de(mod_out) <- react_de(model)[keepReact] + + if(ncol(react_attr(model))>0){ + react_attr(mod_out) <- react_attr(model)[keepReact, ] + } react_num(mod_out) <- length(react_id(mod_out)) @@ -158,19 +163,8 @@ rmReact <- function(model, react, rm_met = TRUE) { allGenes(mod_out) <- ag } - - # reaction to gene mapping - #SrGMbin <- rxnGeneMat(mod_out) != 0 - - #SrGMbindiag <- diag(crossprod(SrGMbin)) - - #keepGenes <- ifelse(SrGMbindiag == 0, FALSE, TRUE) - keepGenes <- sapply(allGenes(model), function(x) match(x, allGenes(mod_out))) - keepGenes <- ifelse(is.na(keepGenes), FALSE, TRUE) - #print(keepGenes) - - rxnGeneMat(mod_out) <- rxnGeneMat(mod_out)[, keepGenes, drop = FALSE] - #print(dim(rxnGeneMat)) + newGeneOrder <- match(allGenes(mod_out), allGenes(model)) + rxnGeneMat(mod_out) <- rxnGeneMat(mod_out)[, newGeneOrder, drop = FALSE] } @@ -208,6 +202,10 @@ rmReact <- function(model, react, rm_met = TRUE) { met_comp(mod_out) <- met_comp(model)[keepMet] met_single(mod_out) <- met_single(model)[keepMet] met_de(mod_out) <- met_de(model)[keepMet] + + if(ncol(met_attr(model))>0){ + met_attr(mod_out) <- met_attr(model)[keepMet, ] + } } else { met_num(mod_out) <- met_num(model) diff --git a/R/settings.R b/R/settings.R index da9dc9e2b7cfe67fe69098ad86a0c9014a14c8d3..7cff1f7780be6984028825ea650bbe7f098bda2e 100644 --- a/R/settings.R +++ b/R/settings.R @@ -42,6 +42,9 @@ SYBIL_SETTINGS <- function(parm, value, ...) { } switch(parm, + "MODELORG_VERSION" = { + stop("this value must not be set by the user!") + }, "SOLVER" = { diff --git a/R/validmodelorg.R b/R/validmodelorg.R index aba3fc6994dd245b0cb5f67f0cf60e6b1fc9a1fb..9ac0dd23a00480b5c75ccb056b4314aea16bc9e7 100644 --- a/R/validmodelorg.R +++ b/R/validmodelorg.R @@ -38,6 +38,12 @@ return("needs an object of class modelorg!") } + versionCheck <- checkVersion(object) + + if(!isTRUE(versionCheck)){ + return(versionCheck) + } + if ((length(mod_id(object)) != 1) || (length(mod_name(object)) != 1)) { return("mod_id and mod_name must have a length of 1!") } @@ -163,6 +169,30 @@ return("Wrong dimension of rxnGeneMat!") } } + + # attributes + + if(0 < ncol(met_attr(object))){ + if(nrow(met_attr(object)) != met){ + return("Wrong nrow of metabolite attributes") + } + } + if(0 < ncol(react_attr(object))){ + if(nrow(react_attr(object)) != react){ + return("Wrong nrow of reaction attributes") + } + } + if(0 < ncol(comp_attr(object))){ + if(nrow(comp_attr(object)) != length(mod_compart(object))){ + return("Wrong nrow of compartment attributes") + } + } + if(0 < ncol(mod_attr(object))){ + if(nrow(mod_attr(object)) != 1){ + return("Wrong nrow of model attributes") + } + } + } return(TRUE) } diff --git a/R/zzz.R b/R/zzz.R index 864d5d0f63c78a07d6a8149ca40ea8f17aa2489c..0dc683d56bcb26be60ced5f674ee03c8236bf822 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -36,6 +36,7 @@ # settings in sybil .SYBILenv$settings <- list( + MODELORG_VERSION = "2.0", SOLVER = "glpkAPI", METHOD = "simplex", TOLERANCE = 1E-6, diff --git a/data/Ec_core.RData b/data/Ec_core.RData index 4030d203e277531c772fa49364dc271910625cde..93dd81cd5a51117c39246a8701d39073edb12bbb 100644 Binary files a/data/Ec_core.RData and b/data/Ec_core.RData differ diff --git a/man/SYBIL_SETTINGS.Rd b/man/SYBIL_SETTINGS.Rd index 75810ed08aa3174c7c8ecfe5d64584fb2dc4b8b2..471edb62f3f9d383641693f7fe44faff2ba42965 100644 --- a/man/SYBIL_SETTINGS.Rd +++ b/man/SYBIL_SETTINGS.Rd @@ -93,14 +93,15 @@ for a particular \code{"SOLVER"}, the corresponding default value will be used in such a case. } - \item{\code{"TOLERANCE"}}{ - Tolerance value.\cr - Default: \code{1E-6}. - } \item{\code{"MAXIMUM"}}{ Absolute maximum value.\cr Default: \code{1000}. } + \item{\code{"MODELORG_VERSION"}}{ + Currtent version of \code{modelorg}-Class.\cr + Value: \code{"2.0"}.\cr + This value must not be changed. + } \item{\code{"ALGORITHM"}}{ Algorithm to use in order to analyze metabolic networks. Possible values are: @@ -145,6 +146,10 @@ (e.g. GLPK).\cr Default: \code{as.data.frame(NA)}. } + \item{\code{"TOLERANCE"}}{ + Tolerance value.\cr + Default: \code{1E-6}. + } } } diff --git a/man/checkOptSol-methods.Rd b/man/checkOptSol-methods.Rd index ae86bd489f38114ee5221b54a4b25853de497a4f..35afd4ea948825f05f81074f0a58705968084906 100644 --- a/man/checkOptSol-methods.Rd +++ b/man/checkOptSol-methods.Rd @@ -50,7 +50,7 @@ } \value{ - TRUE or FALSE if \code{onlywarn} is set to TRUE, otherwisw an object of class + TRUE or FALSE if \code{onlywarn} is set to TRUE, otherwise an object of class \code{\linkS4class{checksol}}. } diff --git a/man/checkVersion-methods.Rd b/man/checkVersion-methods.Rd new file mode 100644 index 0000000000000000000000000000000000000000..528c2759f9ab2de289c4dd38d15e0ec436efce55 --- /dev/null +++ b/man/checkVersion-methods.Rd @@ -0,0 +1,58 @@ +\name{checkVersion-methods} + +\docType{methods} +\encoding{utf8} + +\alias{checkVersion} +\alias{checkVersion-methods} +\alias{checkVersion,modelorg} +\alias{checkVersion,modelorg-method} + +\title{checks Version of modelorg} + +\description{ + Checks the Version of the modelorg. +} + +\usage{ +\S4method{checkVersion}{modelorg}(object) +} + +\section{Methods}{ + \describe{ + \item{\code{signature(object = "modelorg")}}{ + method to use with objects of class \code{\linkS4class{modelorg}}. + } + } +} + +\arguments{ + \item{object}{ + An object of class \code{\linkS4class{modelorg}} or of class + \code{\linkS4class{summaryOptsol}}. + } +} + +\details{ + This method checks whether this instance of a modelorg-Class is of the currently + used version. All methods of sybil create the correct version of modelorg, but + if objects saved to disk may be of an older version. Current version can be + obtained by \code{SYBIL_SETTINGS("VERSION")}. +} + +\author{ + Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de> +} + + +\value{ + Returns \code{TRUE} if the version is correct. Otherwise returns a character + stating the reason. +} + +\seealso{ + Class \code{\linkS4class{modelorg}}, + method \code{\link{upgradeModelorg}} and \code{\link{SYBIL_SETTINGS}} +} + +\keyword{methods} diff --git a/man/modelorg-class.Rd b/man/modelorg-class.Rd index 2b34679cdd15c76cc57bf68f1f1b1baf6445bab1..dfeb47d779bbd9cd0189f77d9ff4c2d13b05cad5 100644 --- a/man/modelorg-class.Rd +++ b/man/modelorg-class.Rd @@ -8,6 +8,10 @@ \alias{allGenes,modelorg-method} \alias{allGenes<-} \alias{allGenes} +\alias{comp_attr<-,modelorg-method} +\alias{comp_attr,modelorg-method} +\alias{comp_attr<-} +\alias{comp_attr} \alias{dim,modelorg-method} \alias{genes<-,modelorg-method} \alias{genes,modelorg-method} @@ -25,6 +29,10 @@ \alias{lowbnd,modelorg-method} \alias{lowbnd<-} \alias{lowbnd} +\alias{met_attr<-,modelorg-method} +\alias{met_attr,modelorg-method} +\alias{met_attr<-} +\alias{met_attr} \alias{met_comp<-,modelorg-method} \alias{met_comp,modelorg-method} \alias{met_comp<-} @@ -49,6 +57,10 @@ \alias{met_single,modelorg-method} \alias{met_single<-} \alias{met_single} +\alias{mod_attr<-,modelorg-method} +\alias{mod_attr,modelorg-method} +\alias{mod_attr<-} +\alias{mod_attr} \alias{mod_compart<-,modelorg-method} \alias{mod_compart,modelorg-method} \alias{mod_compart<-} @@ -75,6 +87,10 @@ \alias{obj_coef} \alias{printObjFunc,modelorg-method} \alias{printObjFunc} +\alias{react_attr<-,modelorg-method} +\alias{react_attr,modelorg-method} +\alias{react_attr<-} +\alias{react_attr} \alias{react_de<-,modelorg-method} \alias{react_de,modelorg-method} \alias{react_de<-} @@ -118,6 +134,10 @@ \alias{uppbnd,modelorg-method} \alias{uppbnd<-} \alias{uppbnd} +\alias{version<-,modelorg-method} +\alias{version,modelorg-method} +\alias{version<-} +\alias{version} \encoding{utf8} @@ -160,6 +180,9 @@ \item{\code{mod_name}:}{ Object of class \code{"character"} indicating the model name. } + \item{\code{version}:}{ + Object of class \code{"character"} indicating the model version. + } \item{\code{mod_id}:}{ Object of class \code{"character"} indicating the model id. } @@ -167,9 +190,16 @@ Object of class \code{"character"} containing a single character string functioning as a unique key to a model object. } + \item{\code{mod_attr}:}{ + Object of class \code{"data.frame"} to store additional attributes of the model. + } \item{\code{mod_compart}:}{ Object of class \code{"character"} containing the model compartments. } + \item{\code{comp_attr}:}{ + Object of class \code{"data.frame"} to store additional attributes for + each compartment. + } \item{\code{met_num}:}{ Object of class \code{"integer"} indicating the number of metabolites. } @@ -182,6 +212,10 @@ \item{\code{met_comp}:}{ Object of class \code{"integer"} containing the metabolites compartment. } + \item{\code{met_attr}:}{ + Object of class \code{"data.frame"} to store additional attributes for + each metabolite. + } \item{\code{met_single}:}{ Object of class \code{"logical"} with length \code{met_num}. Element \code{i} is \code{TRUE}, if metabolite \code{i} appears only once in S. @@ -203,6 +237,10 @@ \item{\code{react_name}:}{ Object of class \code{"character"} containing the reaction names. } + \item{\code{react_attr}:}{ + Object of class \code{"data.frame"} to store additional attributes for + each reaction. + } \item{\code{react_single}:}{ Object of class \code{"logical"} with length \code{react_num}. Element \code{i} is \code{TRUE}, if reaction \code{i} uses metabolites appearing @@ -430,6 +468,12 @@ \item{\code{uppbnd}:}{ \code{signature(object = "modelorg")}: gets the \code{uppbnd} slot. } + \item{\code{version<-}:}{ + \code{signature(object = "modelorg")}: sets the \code{version} slot. + } + \item{\code{version}:}{ + \code{signature(object = "modelorg")}: gets the \code{version} slot. + } } } diff --git a/man/upgradeModelorg.Rd b/man/upgradeModelorg.Rd new file mode 100644 index 0000000000000000000000000000000000000000..45073b33772fd8409c22d26c177bb3267f2c8ece --- /dev/null +++ b/man/upgradeModelorg.Rd @@ -0,0 +1,46 @@ +\name{upgradeModelorg} +\alias{upgradeModelorg} + +\encoding{utf8} + +\title{ + Upgrade modelorg to newer version. +} +\description{ + Performs necessary changes to the object to promote it to a newer version. +} +\usage{ + upgradeModelorg(object) +} + +\arguments{ + \item{object}{ + An object of class \code{\linkS4class{modelorg}}. + } +} + +\details{ + This method performs the necessary changes on a modelorg object to promote + it to a newer version. + + Changes from previous modelorg version (no version slot set) to version 2.0: + Representation in the gprRules slot is now incompatible to the earlier versions. +} + +\value{ + An object of class \code{\linkS4class{modelorg}}, matching the current + version requirements used by sybil. +} + +\author{ + Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de> +} + + +\examples{ + data(Ec_core) + upgradeModelorg(Ec_core) +} + +\keyword{upgrade, version} +