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

new slots for attributes

parent 3d586b72
Branches
No related tags found
No related merge requests found
......@@ -140,6 +140,11 @@ addReact <- function(model,
newS <- S(model)
newMetAttr <- met_attr(model)
newReactAttr <- react_attr(model)
newCompAttr <- comp_attr(model)
newModAttr <- mod_attr(model)
if (isTRUE(addRow)) {
......@@ -181,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
......@@ -211,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)
......@@ -360,6 +376,12 @@ addReact <- function(model,
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 {
......
......@@ -151,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") }
)
......@@ -540,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") }
)
......@@ -600,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") }
)
......@@ -763,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") }
)
......
......@@ -39,18 +39,22 @@ 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
......@@ -111,6 +115,10 @@ 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))
......@@ -206,7 +214,6 @@ setReplaceMethod("mod_compart", signature(object = "modelorg"),
}
)
# number of metabolites
setMethod("met_num", signature(object = "modelorg"),
function(object) {
......@@ -565,6 +572,64 @@ setReplaceMethod("version", signature(object = "modelorg"),
}
)
# 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 #
......
......@@ -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 = "()&|~") {
......
......@@ -25,8 +25,8 @@
################################################
# 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 = "")
......
......@@ -26,7 +26,7 @@
# Function: readTSVmod
#
#
#
# 2016-05-18 CJF: format of gprRules was changed.
readTSVmod <- function(prefix, suffix,
reactList, metList = NA, modDesc = NA,
......@@ -950,7 +950,7 @@ readTSVmod <- function(prefix, suffix,
geneInd <- match(Rgenes[[i]], allGenes)
rxnGeneMat[i, geneInd] <- TRUE
# not needed for version 2.0 modelorgs
# 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 = "")
......
......@@ -134,6 +134,10 @@ rmReact <- function(model, react, rm_met = TRUE) {
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))
# stoichiometric matrix
......@@ -210,6 +214,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)
......
......@@ -33,16 +33,24 @@
upgradeModelorg <- function(object){
stopifnot(is(object, "modelorg"))
if(!.hasSlot(object, "version")){
if(!.hasSlot(object, "version") || compareVersion(version(object), "2.0") == -1){
# object is from a time before versions were introduced.
# just add version slot and run again.
# just add version slot
object@version <- "2.0"
# update gprRules to new format
rules <- lapply(gpr(object), .parseBoolean)
genes(object) <- sapply(rules, "[[", "gene")
gprRules(object) <- sapply(rules, "[[", "rule")
#recursively upgrad to latest version.
# set attribute slots
react_attr(object) <- data.frame()
comp_attr(object) <- data.frame()
met_attr(object) <- data.frame()
mod_attr(object) <- data.frame()
#recursively upgrade to latest version.
return(upgradeModelorg(object))
}
......
......@@ -169,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)
}
No preview for this file type
......@@ -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<-}
......@@ -174,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.
}
......@@ -189,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.
......@@ -210,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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment