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

merged master with writeSBML branch

parents 4f3015c4 3b8f5e09
No related branches found
No related tags found
No related merge requests found
Package: sybilSBML
Type: Package
Title: SBML Integration in Package 'Sybil'
Version: 2.0.11
Date: 2016-06-06
Version: 3.0.1
Date: 2016-12-16
Authors@R: c(person(c("C.", "Jonathan"), "Fritzemeier", role = c("cre", "ctb"), email = "clausjonathan.fritzemeier@uni-duesseldorf.de"),
person("Gabriel", "Gelius-Dietrich", role = c("aut", "ctb")),
person("Deya", "Alzoubi", role = "ctb"))
person("Deya", "Alzoubi", role = "ctb"),
person("Ardalan", "Habil", role = "ctb"))
Maintainer: C. Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de>
Depends: R (>= 2.14.2), Matrix, sybil (>= 2.0.0)
Imports: methods
Description: 'SBML' (Systems Biology Markup Language) integration in 'sybil'. Many constraint based metabolic models are published in 'SBML' format ('*.xml'). Herewith is the ability to read and check 'SBML' files in 'sybil' provided.
Description: 'SBML' (Systems Biology Markup Language) with FBC (Flux Balance Constraints) integration in 'sybil'. Many constraint based metabolic models are published in 'SBML' format ('*.xml'). Herewith is the ability to read, write, and check 'SBML' files in 'sybil' provided.
License: GPL-3 | file LICENSE
LazyLoad: yes
Collate: generics.R sbmlPtrClass.R sbmlErrorClass.R sybilSBML.R
uglyHack.R readSBMLmod.R zzz.R
Packaged: 2015-06-06 07:11:55 UTC; jonathan
Packaged: 2016-12-16 07:11:55 UTC; jonathan
Author: C. Jonathan Fritzemeier [cre, ctb],
Gabriel Gelius-Dietrich [aut, ctb],
Deya Alzoubi [ctb]
Deya Alzoubi [ctb],
Ardalan Habil [ctb]
NeedsCompilation: yes
Repository: CRAN
......@@ -48,5 +48,9 @@ getSBMLunitDefinitionsList,
getSBMLCompartList,
getSBMLSpeciesList,
getSBMLReactionsList,
readSBMLmod
readSBMLmod,
writeSBML,
getSBMLFbcversion,
getSBMLmodNotes,
getSBMLmodAnnotation
)
......@@ -247,7 +247,13 @@ parseNotesReact <- function(notes) {
gpr <- sub("GENE[_ ]?ASSOCIATION: *", "", fields_str[j])
gene_rule <- sybil:::.parseBoolean(gpr)
#print(gene_rule)
}#Ardalan Habil
else if (grepl("GPR[_ ]?ASSOCIATION", fields_str[j])) {
gpr <- sub("GPR[_ ]?ASSOCIATION: *", "", fields_str[j])
gene_rule <- sybil:::.parseBoolean(gpr)
}
if (charmatch("SUBSYSTEM", fields_str[j], nomatch = -1) != -1) {
subSyst <- sub("SUBSYSTEM: *", "", fields_str[j])
subSyst <- sub("^S_", "", subSyst, perl = TRUE)
......@@ -283,6 +289,14 @@ sbmldoc <- openSBMLfile(filename)
message("OK")
# warning if new Version/Level/
SBMLlevel<- getSBMLlevel(sbmldoc)
SBMLversion<- getSBMLversion(sbmldoc)
FBCversion<-getSBMLFbcversion(sbmldoc)
if(SBMLlevel == 3 && SBMLversion > 1)
warning(paste("No support for Level 3 Version ",SBMLversion))
if (FBCversion > 2)
warning(paste("No support for Fbc Version ",FBCversion))
#------------------------------------------------------------------------------#
# check the model #
......@@ -380,6 +394,7 @@ if (mdesc == filename) {
sybil::mod_desc(mod) <- mdesc
#------------------------------------------------------------------------------#
# units #
#------------------------------------------------------------------------------#
......@@ -398,7 +413,7 @@ if (is.null(compartmentsList)) {
}
missingId(compartmentsList)
sybil::mod_compart(mod) <- compartmentsList[["id"]]
comp_tmp_id <- compartmentsList[["id"]]
#------------------------------------------------------------------------------#
......@@ -430,6 +445,7 @@ missingId(metabolitesList)
metSpIds <- metabolitesList[["id"]]
#nummet <- getSBMLnumSpecies(sbmlmod)
if (isTRUE(bndCond)) {
metSpBnd <- metabolitesList[["boundaryCondition"]]
met_id_pos <- !metSpBnd
......@@ -485,12 +501,20 @@ gpr <- character(numreact)
hasNotes <- FALSE
hasAnnot <- FALSE
#FBC contraints @Ardalan Habil
fbclowbnd<-reactionsList[["fbc_lowbnd"]]
fbcuppbnd<-reactionsList[["fbc_uppbnd"]]
fbcgprRules<-reactionsList[["fbc_gprRules"]]
fbcObjectives<-reactionsList[["fbc_Objectives"]]
for (i in 1 : numreact) {
# the notes/annotations field
notes <- reactionsList[["notes"]][i]
annot <- reactionsList[["annotation"]][i]
# Notes und Annotation can be null ( @Ardalan Habil)
if(!is.null( reactionsList[["notes"]]))
if (nchar(notes) > 0) {
hasNotes <- TRUE
......@@ -504,7 +528,7 @@ for (i in 1 : numreact) {
}
else {
if(!is.null( reactionsList[["annotation"]]))
if (nchar(annot) > 0) {
hasAnnot <- TRUE
pn <- regexpr("Pathway Name: [^<]+", annot, perl = TRUE)
......@@ -514,6 +538,17 @@ for (i in 1 : numreact) {
}
fbcgene_rule <- NA
if ( !is.null(fbcgprRules))
{
fbcgene_rule<- sybil:::.parseBoolean(fbcgprRules[i])
genes[[i]] <- fbcgene_rule$gene # list of genes
rules[i] <- fbcgene_rule$rule # rules
gpr[i] <- fbcgprRules[i]
}
# Check here if reactants and products lists exist, same for the stoichiometry slot
# Entries for S -- the reactants
......@@ -565,6 +600,16 @@ for (i in 1 : numreact) {
# }
# the constraints
#FBC contraints @Ardalan Habil
if ( !is.null(fbclowbnd) && !is.null(fbcuppbnd))
{
lbnd[i] <- checkupplowbnd(fbclowbnd[i])
ubnd[i] <- checkupplowbnd(fbcuppbnd[i])
}
#read from kinetic_law if fbc is empty
else
{
parm <- reactionsList[["kinetic_law"]][[i]]
if (is.null(parm)) {
ubnd[i] <- def_bnd
......@@ -591,9 +636,15 @@ for (i in 1 : numreact) {
# reduced cost? (sbml file)
}
}
}
#FBC Objective @Ardalan Habil
if(!is.null(fbcObjectives))
{
ocof[i]<-as.numeric(fbcObjectives[i])
}
}
# ---------------------------------------------------------------------------- #
# search for unused metabolites and unused reactions
......@@ -877,7 +928,7 @@ else {
rules <- rules[SKIP_REACTION]
gpr <- gpr[SKIP_REACTION]
if (isTRUE(hasNotes)) {
if (isTRUE(hasNotes) || !is.null(fbcgprRules) ) {
message("GPR mapping ... ", appendLF = FALSE)
#allGenes <- unique(allGenes)
......@@ -898,13 +949,12 @@ else {
geneInd <- match(genes[[i]], allGenes)
rxnGeneMat[i, geneInd] <- TRUE
# no use because new gprRule format
# for (j in 1 : length(geneInd)) {
# pat <- paste("x(", j, ")", sep = "")
# repl <- paste("x[", geneInd[j], "]", sep = "")
#
# rules[i] <- gsub(pat, repl, rules[i], fixed = TRUE)
# }
for (j in 1 : length(geneInd)) {
pat <- paste("x(", j, ")", sep = "")
repl <- paste("x[", geneInd[j], "]", sep = "")
rules[i] <- gsub(pat, repl, rules[i], fixed = TRUE)
}
}
}
......@@ -970,6 +1020,63 @@ react_name_tmp <- sub( "\\s+$", "", react_name_tmp, perl = TRUE)
sybil::react_name(mod) <- react_name_tmp
#------------------------------------------------------------------------------#
# Reaction Attr @Ardalan #
#------------------------------------------------------------------------------#
# Test for new Slots
if( .hasSlot(mod,"mod_attr") && .hasSlot(mod,"comp_attr") && .hasSlot(mod,"met_attr") && .hasSlot(mod,"react_attr") )
newSybil<-TRUE
else newSybil<-FALSE
numreact<-nummet <- sum(SKIP_REACTION)
reactannotation <- reactionsList[["annotation"]][SKIP_REACTION]
reactnotes <- reactionsList[["notes"]][SKIP_REACTION]
if(newSybil)
{
sybil::react_attr(mod) <-data.frame(row.names=1:numreact)
#Speed optimierung durch notes NULL falls nichts drin steht
if( !is.null(reactannotation) && length(reactannotation)==numreact )sybil::react_attr(mod)[['annotation']]<-reactannotation
if( !is.null(reactnotes) && length(reactnotes)==numreact )sybil::react_attr(mod)[['notes']]<-reactnotes
}
#------------------------------------------------------------------------------#
# Model Attr @Ardalan #
#------------------------------------------------------------------------------#
modanno<-getSBMLmodAnnotation(sbmlmod)
modnotes<-getSBMLmodNotes(sbmlmod)
if(newSybil)
{
sybil::mod_attr(mod) <-data.frame(row.names=1)
if(nchar(modanno)>1)sybil::mod_attr(mod)[['annotation']]<-modanno
if(nchar(modnotes)>1)sybil::mod_attr(mod)[['notes']]<-modnotes
}
#------------------------------------------------------------------------------#
# compartments Attr @Ardalan #
#------------------------------------------------------------------------------#
# Define SKIP_COMPARTMENT FALSE= HAS NO REFERENCE
met_comp_tmp <- metabolitesList[["compartment"]][met_id_pos][SKIP_METABOLITE]
SKIP_COMPARTMENT<- comp_tmp_id %in% unique(met_comp_tmp)
sybil::mod_compart(mod) <- comp_tmp_id[SKIP_COMPARTMENT]
numcom<-length(mod_compart(mod))
comannotation <- compartmentsList[["annotation"]][SKIP_COMPARTMENT]
comnotes <- compartmentsList[["notes"]][SKIP_COMPARTMENT]
if(newSybil)
{
sybil::comp_attr(mod) <-data.frame(row.names=1:numcom)
if( !is.null(comannotation) && length(comannotation)==numcom )sybil::comp_attr(mod)[['annotation']]<-comannotation
if( !is.null(comnotes) && length(comnotes)==numcom )sybil::comp_attr(mod)[['notes']]<-comnotes
}
#------------------------------------------------------------------------------#
# metabolite id's #
#------------------------------------------------------------------------------#
......@@ -985,7 +1092,7 @@ sybil::met_id(mod) <- gsub("-", "_", met_id_tmp, fixed = TRUE)
# metabolite compartments #
#------------------------------------------------------------------------------#
met_comp_tmp <- metabolitesList[["compartment"]][met_id_pos][SKIP_METABOLITE]
#met_comp_tmp <- metabolitesList[["compartment"]][met_id_pos][SKIP_METABOLITE]
sybil::met_comp(mod) <- match(met_comp_tmp, sybil::mod_compart(mod))
......@@ -1002,6 +1109,69 @@ met_name_tmp <- sub( "\\s+$", "", met_name_tmp, perl = TRUE)
sybil::met_name(mod) <- met_name_tmp
#------------------------------------------------------------------------------#
# metabolite attr @Ardalan Habil #
#------------------------------------------------------------------------------#
#ChemicalFormula Charge Notes Annotation MetaID @Ardalan Habil
metformula <- metabolitesList[["chemicalFormula"]][met_id_pos][SKIP_METABOLITE]
metcharge <- metabolitesList[["charge"]][met_id_pos][SKIP_METABOLITE]
metnotes <- metabolitesList[["notes"]][met_id_pos][SKIP_METABOLITE]
metannotation <- metabolitesList[["annotation"]][met_id_pos][SKIP_METABOLITE]
metchargenote<-NULL
metformulanote<-NULL
# check metnotes for Formula and Charge
if( !is.null(metnotes) && length(metnotes==nummet))
{
pn <- regexpr("FORMULA: [^<]+", metnotes, perl = TRUE)
metformulanote <- substr(metnotes, (pn+9), pn + ((attr(pn, "match.length"))-1))
pn <- regexpr("CHARGE: [^<]+", metnotes, perl = TRUE)
metchargenote <- substr(metnotes, (pn+8), pn + ((attr(pn, "match.length"))-1))
metchargenote <- as.integer(metchargenote)
metchargenote[is.na(metchargenote)] <- 0
}
nummet <- sum(SKIP_METABOLITE)
if(newSybil)
{
# save attributes to met_attr slot
sybil::met_attr(mod) <-data.frame(row.names=1:nummet)
if( !is.null(metformula) && length(metformula)==nummet)
{sybil::met_attr(mod)[['chemicalFormula']]<-metformula}
else{
if(length(metformulanote)==nummet)
{ if(max(nchar(metformulanote)) >0)
sybil::met_attr(mod)[['chemicalFormula']]<-metformulanote
}
}
if( !is.null(metcharge) && length(metcharge)==nummet && sum(metcharge)!=0)
{sybil::met_attr(mod)[['charge']]<-metcharge}
else{
if( length(metchargenote)==nummet)
{ if(max(nchar(metchargenote)) >0)
sybil::met_attr(mod)[['charge']]<-metchargenote
}
}
if( !is.null(metnotes) && length(metnotes)==nummet)sybil::met_attr(mod)[['notes']]<-metnotes
if( !is.null(metannotation) && length(metannotation)==nummet)sybil::met_attr(mod)[['annotation']]<-metannotation
# Save boundaryCondition when bndCond=FALSE
if (!isTRUE(bndCond)) {
metBnd <- metabolitesList[["boundaryCondition"]][met_id_pos][SKIP_METABOLITE]
# When all metBnd = False -> metabolite removed by extMetFlag
if( !is.null(metBnd) && length(metBnd)==nummet && !all(metBnd == FALSE) )sybil::met_attr(mod)[['boundaryCondition']]<-metBnd
}
}
#------------------------------------------------------------------------------#
# check reversibilities #
#------------------------------------------------------------------------------#
......
......@@ -124,6 +124,17 @@ getSBMLversion <- function(sbmlf) {
return(version)
}
#------------------------------------------------------------------------------#
getSBMLFbcversion <- function(sbmlf) {
version <- .Call("getSBMLFbcversion", PACKAGE = "sybilSBML",
sbmlPointer(sbmlf)
)
return(version)
}
#------------------------------------------------------------------------------#
......@@ -186,6 +197,28 @@ getSBMLmodName <- function(sbmlm) {
return(modn)
}
#------------------------------------------------------------------------------#
getSBMLmodNotes <- function(sbmlm) {
modnotes <- .Call("getSBMLmodNotes", PACKAGE = "sybilSBML",
sbmlPointer(sbmlm)
)
return(modnotes)
}
#------------------------------------------------------------------------------#
getSBMLmodAnnotation <- function(sbmlm) {
modanno <- .Call("getSBMLmodAnnotation", PACKAGE = "sybilSBML",
sbmlPointer(sbmlm)
)
return(modanno)
}
#------------------------------------------------------------------------------#
......@@ -271,10 +304,272 @@ getSBMLReactionsList <- function(sbmlm) {
}
#------------------------------------------------------------------------------#
#export mod to SBML
deformatSBMLid <- function(idstr) {
idstr <- gsub("-", "_DASH_", idstr, fixed = TRUE)
idstr <- gsub("(", "_LPAREN_", idstr, fixed = TRUE)
idstr <- gsub(")", "_RPAREN_", idstr, fixed = TRUE)
idstr <- gsub("[", "_", idstr, fixed = TRUE)
idstr <- gsub("]", "", idstr, fixed = TRUE)
idstr <- gsub(",", "_COMMA_", idstr, fixed = TRUE)
idstr <- gsub(".", "_PERIOD_", idstr, fixed = TRUE)
idstr <- gsub("'", "_APOS_", idstr, fixed = TRUE)
idstr <- sub("\\(e\\)$", "_e_", idstr)
idstr <- gsub("-", "_", idstr, fixed = TRUE)
return(idstr)
}
deformatGene<-function(idstr) {
idstr<-gsub("\\((\\S+)\\)", "\\1", idstr)
#idstr <- gsub("( ", "(", idstr, fixed = TRUE)
#idstr <- gsub(" (", "(", idstr, fixed = TRUE)
#idstr <- gsub(") ", ")", idstr, fixed = TRUE)
#idstr <- gsub(" )", ")", idstr, fixed = TRUE)
idstr <- gsub(":", "_", idstr, fixed = TRUE)
return(idstr)
}
writeSBML<- function(morg=NULL,level=2,version=4,fbcLevel=0,filename="export.xml",recoverExtMet=FALSE,printNotes=TRUE,printAnnos=TRUE,validation=FALSE ){
if(class(morg)!="modelorg"){
stop("morg has to be of class modelorg\n")
}
###right
if(level==1)
{
# test if Matrix has no double values
if( !all( S(morg) == floor(S(morg))) ) warning("Level 1 does not support double values")
fbcLevel=0
if(version != 2)
{
warning("just Level 1 Version 2 will be supported")
version=2
}
}else if (level==2)
{
fbcLevel=0
if(version >5)
{
warning("Level 2 Version 5 will be supported")
version=5
}
if(version < 1)
{
warning("Level 2 Version 1 will be supported")
version=1
}
}
else if (level==3)
{ if(fbcLevel >2)fbcLevel=2
if(version != 1)
{
print("Level 3 Version 1 will be supported")
version=1
}
}else {
stop(" Support just for Level 1,2 and 3 \n")
}
##All GENES###
allgenes<- unique(unlist(genes(morg)))
allgenes<-allgenes[allgenes != ""]
##EXCHANGE REACTIONS##
ex <- findExchReact(morg)
ex_react<-NULL
# if recoverExtMet== FALSE => null for ex_react
if( (!is.null(ex)) && (recoverExtMet) )
{
if(!(all(diag(S(morg)[met_pos(ex), react_pos(ex)])==-1)))
stop("exchange reactions with Scoeff different than -1\n")
ex_react<-as.integer(react_pos(ex))
}
### Build wrapper for C Function #####
##Met Attribute###
com_meta_id<- NULL
met_meta_id<- NULL
com_notes <- NULL
com_annotation<- NULL
met_notes<- NULL
met_anno<- NULL
met_bnd<- NULL
met_charge<-NULL
met_formula<-NULL
react_notes<-NULL
react_anno<-NULL
mod_notes<-NULL
mod_anno<-NULL
#subsystem
# is subsystem Empty
if(length( colnames(subSys(morg)))==1 && colnames(subSys(morg))[1]=="" ) modhasubSys<-FALSE
else modhasubSys<-TRUE
newsubS<- NULL
if( .hasSlot(morg,"mod_attr") && .hasSlot(morg,"comp_attr") && .hasSlot(morg,"met_attr") && .hasSlot(morg,"react_attr") )
newSybil<-TRUE
else newSybil<-FALSE
### Start newSybil attr
if(newSybil)
{
if(("notes" %in% colnames(mod_attr(morg))) && (printNotes) ) mod_notes<-as.character(mod_attr(morg)[['notes']])
if(("annotation" %in% colnames(mod_attr(morg))) && (printAnnos) ) mod_annotation<-as.character(mod_attr(morg)[['annotation']])
if(("notes" %in% colnames(comp_attr(morg))) && (printNotes) ) com_notes<-as.character(as.list((comp_attr(morg)[['notes']])))
if(("annotation" %in% colnames(comp_attr(morg))) && (printAnnos) ) com_annotation<-as.character(as.list((comp_attr(morg)[['annotation']])))
if("charge" %in% colnames(met_attr(morg))) met_charge<- as.integer(as.list((met_attr(morg)[['charge']])))
if("chemicalFormula" %in% colnames(met_attr(morg))) met_formula<-as.character(as.list((met_attr(morg)[['chemicalFormula']])))
if(("annotation" %in% colnames(met_attr(morg))) && (printAnnos)) met_anno<-as.character(as.list((met_attr(morg)[['annotation']])))
if("boundaryCondition" %in% colnames(met_attr(morg))) met_bnd<-as.logical(as.list((met_attr(morg)[['boundaryCondition']])))
if(("notes" %in% colnames(met_attr(morg))) && (printNotes) )
{ # delete Formular and charge from notes to do
met_notes<-as.character(as.list((met_attr(morg)[['notes']])))
if (!is.null(met_charge) || !is.null(met_formula))
{
for ( i in 1:met_num(morg))
{
if(nchar(met_notes[i])> 8)
{
# Have Assocation in Notes?yes: replace no: append
if (regexpr("html:p", met_notes[i], fixed = TRUE) == -1)tag <- "p"
else tag <- "html:p"
if (!is.null(met_formula))
{
haveform<-grepl("FORMULA: [^<]+",met_notes[i])
#Have Gene if not ->no need to write in FBC2
if(haveform)
{
if(fbcLevel==0)met_notes[i]<-sub("FORMULA: [^<]+",paste("FORMULA: ",met_formula[i], sep = ""), met_notes[i], perl = TRUE)
else met_notes[i]<-sub(paste("<",tag,">","FORMULA: [^<]+","</",tag,">",sep = ""),"",met_notes[i], perl = TRUE)
}
else if(fbcLevel==0) met_notes[i]<-gsub("</notes>",paste("<",tag,">","FORMULA: ",met_formula[i],"</",tag,">","\n</notes>",sep = ""),met_notes[i])
}
if (!is.null(met_charge))
{
havecharge<-grepl("CHARGE: [^<]+",met_notes[i])
#Have Subsystem
if(havecharge)
{
if(fbcLevel !=0 || (level==2 && version==1 ))
met_notes[i]<-sub(paste("<",tag,">","CHARGE: [^<]+","</",tag,">",sep = ""),"",met_notes[i], perl = TRUE)
else met_notes[i]<-sub("CHARGE: [^<]+",paste("CHARGE: ",met_charge[i], sep = ""), met_notes[i], perl = TRUE)
}
else if(fbcLevel==0) if(level!=2 && version!=1) met_notes[i]<-gsub("</notes>",paste("<",tag,">","CHARGE: ",met_charge[i],"</",tag,">","\n</notes>",sep = ""),met_notes[i])
}
}
}
}
}
if(("annotation" %in% colnames(react_attr(morg))) && (printAnnos)) react_anno<-as.character(as.list((react_attr(morg)[['annotation']])))
# Merge Notes with "our" Notes and make sure gpr Rules from gpr
if(("notes" %in% colnames(react_attr(morg))) && (printNotes))
{
react_notes<-as.character(as.list((react_attr(morg)[['notes']])))
# using
# SubSystem EXISTIERT nicht colnames(subSys(ec))
for ( i in 1:react_num(morg))
{
# using the for loop
if(modhasubSys)newsubS[i]<- paste(names(which(subSys(morg)[i,])), collapse=", ")
if(nchar(react_notes[i])> 8)
{
# Have Association in Notes? yes: replace no: append
if (regexpr("html:p", react_notes[i], fixed = TRUE) == -1)tag <- "p"
else tag <- "html:p"
havegene<-grepl("GENE[_ ]?ASSOCIATION: [^<]+",react_notes[i])
havesub<-grepl("SUBSYSTEM: [^<]+",react_notes[i])
#Have Gene if not ->no need to write in FBC2
if(havegene)
{
if(fbcLevel==2) react_notes[i]<-sub(paste("<",tag,">","GENE[_ ]?ASSOCIATION: [^<]+","</",tag,">",sep = ""),"",react_notes[i], perl = TRUE)
else react_notes[i]<-sub("GENE[_ ]?ASSOCIATION: [^<]+",paste("GENE_ASSOCIATION: ",gpr(morg)[i], sep = ""), react_notes[i], perl = TRUE)
}
else if(fbcLevel!=2)react_notes[i]<-gsub("</notes>",paste("<",tag,">","GENE_ASSOCIATION: ",gpr(morg)[i],"</",tag,">","\n</notes>",sep = ""),react_notes[i])
#Have Subsystem
if(havesub)react_notes[i]<-sub("SUBSYSTEM: [^<]+",paste("SUBSYSTEM: ",newsubS[i], sep = ""), react_notes[i], perl = TRUE)
else if(modhasubSys) react_notes[i]<-gsub("</notes>",paste("<",tag,">","SUBSYSTEM: ",newsubS[i],"</",tag,">","\n</notes>",sep = ""),react_notes[i])
}
}
}
} ####END newSybil attr
# Subsystem
if(is.null(newsubS) && !(modhasubSys) ) for ( i in 1:react_num(morg)) {newsubS[i]<- paste(names(which(subSys(morg)[i,])), collapse=", ")}
newmet_id <- paste0("M_", (deformatSBMLid(met_id(morg))))
#newmet_id <- sub("\\[(\\w)\\]$", "_\\1", newmet_id) # append compartment id, if in postfix with square brkts
newreact_id <- paste0("R_", deformatSBMLid(react_id(morg)))
newmet_comp<-mod_compart(morg)[met_comp(morg)]
success <-.Call("exportSBML", PACKAGE = "sybilSBML",
as.integer(version),
as.integer(level),
as.integer(fbcLevel),
as.character(filename),
SYBIL_SETTINGS("MAXIMUM"),
as.character(mod_desc(morg)),
as.character(mod_name(morg)),
as.character(mod_compart(morg)),
as.character(newmet_id),
as.character(met_name(morg)),
as.character(newmet_comp),
met_formula,
met_charge,
as.character(newreact_id),
as.character(react_name(morg)),
as.logical(react_rev(morg)),
as.numeric(lowbnd(morg)),
as.numeric(uppbnd(morg)),
as.integer(obj_coef(morg)),
as.character(newsubS),
as.character(deformatGene(gpr(morg))),
as.numeric(shrinkMatrix(morg,j=1:react_num(morg))),
mod_notes,
mod_anno,
com_notes,
com_annotation,
met_notes,
met_anno,
met_bnd,
react_notes,
react_anno,
ex_react,
as.character(deformatGene(allgenes))
)
# SUCESS MESSAGES
if(success)
{
message(paste("Wrote file ",filename,"\n",sep=""), appendLF = FALSE);
if (validation)print(validateSBMLdocument(filename));
}
else message(paste("Could not write file ",filename,"\n",sep=""), appendLF = FALSE);
return (success)
}
\ No newline at end of file
File added
#! /bin/sh
# Guess values for system-dependent variables and create Makefiles.
# Generated by GNU Autoconf 2.69 for sybilSBML 2.0.8.
# Generated by GNU Autoconf 2.69 for sybilSBML 3.0.0.
#
# Report bugs to <geliudie@uni-duesseldorf.de>.
# Report bugs to <clausjonathan.fritzemeier@uni-duesseldorf.de>.
#
#
# Copyright (C) 1992-1996, 1998-2012 Free Software Foundation, Inc.
......@@ -267,8 +267,8 @@ fi
$as_echo "$0: be upgraded to zsh 4.3.4 or later."
else
$as_echo "$0: Please tell bug-autoconf@gnu.org and
$0: geliudie@uni-duesseldorf.de about your system,
$0: including any error possibly output before this
$0: clausjonathan.fritzemeier@uni-duesseldorf.de about your
$0: system, including any error possibly output before this
$0: message. Then install a modern shell, or manually run
$0: the script under such a shell if you do have one."
fi
......@@ -580,9 +580,9 @@ MAKEFLAGS=
# Identity of this package.
PACKAGE_NAME='sybilSBML'
PACKAGE_TARNAME='sybilsbml'
PACKAGE_VERSION='2.0.8'
PACKAGE_STRING='sybilSBML 2.0.8'
PACKAGE_BUGREPORT='geliudie@uni-duesseldorf.de'
PACKAGE_VERSION='3.0.0'
PACKAGE_STRING='sybilSBML 3.0.0'
PACKAGE_BUGREPORT='clausjonathan.fritzemeier@uni-duesseldorf.de'
PACKAGE_URL=''
# Factoring default headers for most tests.
......@@ -1230,7 +1230,7 @@ if test "$ac_init_help" = "long"; then
# Omit some internal or obsolete options to make the list less imposing.
# This message is too long to be a string in the A/UX 3.1 sh.
cat <<_ACEOF
\`configure' configures sybilSBML 2.0.8 to adapt to many kinds of systems.
\`configure' configures sybilSBML 3.0.0 to adapt to many kinds of systems.
Usage: $0 [OPTION]... [VAR=VALUE]...
......@@ -1291,7 +1291,7 @@ fi
if test -n "$ac_init_help"; then
case $ac_init_help in
short | recursive ) echo "Configuration of sybilSBML 2.0.8:";;
short | recursive ) echo "Configuration of sybilSBML 3.0.0:";;
esac
cat <<\_ACEOF
......@@ -1315,7 +1315,7 @@ Some influential environment variables:
Use these variables to override the choices made by `configure' or to help
it to find libraries and programs with nonstandard names/locations.
Report bugs to <geliudie@uni-duesseldorf.de>.
Report bugs to <clausjonathan.fritzemeier@uni-duesseldorf.de>.
_ACEOF
ac_status=$?
fi
......@@ -1378,7 +1378,7 @@ fi
test -n "$ac_init_help" && exit $ac_status
if $ac_init_version; then
cat <<\_ACEOF
sybilSBML configure 2.0.8
sybilSBML configure 3.0.0
generated by GNU Autoconf 2.69
Copyright (C) 2012 Free Software Foundation, Inc.
......@@ -1537,9 +1537,9 @@ $as_echo "$as_me: WARNING: $2: see the Autoconf documentation" >&2;}
$as_echo "$as_me: WARNING: $2: section \"Present But Cannot Be Compiled\"" >&2;}
{ $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: proceeding with the compiler's result" >&5
$as_echo "$as_me: WARNING: $2: proceeding with the compiler's result" >&2;}
( $as_echo "## ------------------------------------------ ##
## Report this to geliudie@uni-duesseldorf.de ##
## ------------------------------------------ ##"
( $as_echo "## ----------------------------------------------------------- ##
## Report this to clausjonathan.fritzemeier@uni-duesseldorf.de ##
## ----------------------------------------------------------- ##"
) | sed "s/^/$as_me: WARNING: /" >&2
;;
esac
......@@ -1676,11 +1676,78 @@ fi
as_fn_set_status $ac_retval
} # ac_fn_c_try_link
# ac_fn_c_check_func LINENO FUNC VAR
# ----------------------------------
# Tests whether FUNC exists, setting the cache variable VAR accordingly
ac_fn_c_check_func ()
{
as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack
{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5
$as_echo_n "checking for $2... " >&6; }
if eval \${$3+:} false; then :
$as_echo_n "(cached) " >&6
else
cat confdefs.h - <<_ACEOF >conftest.$ac_ext
/* end confdefs.h. */
/* Define $2 to an innocuous variant, in case <limits.h> declares $2.
For example, HP-UX 11i <limits.h> declares gettimeofday. */
#define $2 innocuous_$2
/* System header to define __stub macros and hopefully few prototypes,
which can conflict with char $2 (); below.
Prefer <limits.h> to <assert.h> if __STDC__ is defined, since
<limits.h> exists even on freestanding compilers. */
#ifdef __STDC__
# include <limits.h>
#else
# include <assert.h>
#endif
#undef $2
/* Override any GCC internal prototype to avoid an error.
Use char because int might match the return type of a GCC
builtin and then its argument prototype would still apply. */
#ifdef __cplusplus
extern "C"
#endif
char $2 ();
/* The GNU C library defines this for functions which it implements
to always fail with ENOSYS. Some functions are actually named
something starting with __ and the normal name is an alias. */
#if defined __stub_$2 || defined __stub___$2
choke me
#endif
int
main ()
{
return $2 ();
;
return 0;
}
_ACEOF
if ac_fn_c_try_link "$LINENO"; then :
eval "$3=yes"
else
eval "$3=no"
fi
rm -f core conftest.err conftest.$ac_objext \
conftest$ac_exeext conftest.$ac_ext
fi
eval ac_res=\$$3
{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5
$as_echo "$ac_res" >&6; }
eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno
} # ac_fn_c_check_func
cat >config.log <<_ACEOF
This file contains any messages produced by compilers while
running configure, to aid debugging if configure makes a mistake.
It was created by sybilSBML $as_me 2.0.8, which was
It was created by sybilSBML $as_me 3.0.0, which was
generated by GNU Autoconf 2.69. Invocation command line was
$ $0 $@
......@@ -3528,6 +3595,101 @@ else
fi
{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for readSBML in -lsbml" >&5
$as_echo_n "checking for readSBML in -lsbml... " >&6; }
if ${ac_cv_lib_sbml_readSBML+:} false; then :
$as_echo_n "(cached) " >&6
else
ac_check_lib_save_LIBS=$LIBS
LIBS="-lsbml $LIBS"
cat confdefs.h - <<_ACEOF >conftest.$ac_ext
/* end confdefs.h. */
/* Override any GCC internal prototype to avoid an error.
Use char because int might match the return type of a GCC
builtin and then its argument prototype would still apply. */
#ifdef __cplusplus
extern "C"
#endif
char readSBML ();
int
main ()
{
return readSBML ();
;
return 0;
}
_ACEOF
if ac_fn_c_try_link "$LINENO"; then :
ac_cv_lib_sbml_readSBML=yes
else
ac_cv_lib_sbml_readSBML=no
fi
rm -f core conftest.err conftest.$ac_objext \
conftest$ac_exeext conftest.$ac_ext
LIBS=$ac_check_lib_save_LIBS
fi
{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_sbml_readSBML" >&5
$as_echo "$ac_cv_lib_sbml_readSBML" >&6; }
if test "x$ac_cv_lib_sbml_readSBML" = xyes; then :
cat >>confdefs.h <<_ACEOF
#define HAVE_LIBSBML 1
_ACEOF
LIBS="-lsbml $LIBS"
else
as_fn_error $? "Could not link to libSBML:
use --with-sbml-lib or PKG_LIBS to specify the library path and the libraries to pass to the linker." "$LINENO" 5
fi
ac_fn_c_check_header_compile "$LINENO" "sbml/packages/fbc/common/FbcExtensionTypes.h" "ac_cv_header_sbml_packages_fbc_common_FbcExtensionTypes_h" "#include <sbml/SBMLTypes.h>
"
if test "x$ac_cv_header_sbml_packages_fbc_common_FbcExtensionTypes_h" = xyes; then :
else
as_fn_error $? "Could not find specific FBC header of libSBML:
make sure your libSBML version is >= 5.13." "$LINENO" 5
fi
#AC_CHECK_LIB([sbml], [SBMLExtensionRegistry_getRegisteredPackages], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
for ac_func in SBase_getPlugin SBMLExtensionRegistry_getRegisteredPackages GeneProductAssociation_setAssociation FbcReactionPlugin_getLowerFluxBound
do :
as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh`
ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var"
if eval test \"x\$"$as_ac_var"\" = x"yes"; then :
cat >>confdefs.h <<_ACEOF
#define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1
_ACEOF
else
as_fn_error $? "Could not find specific FBC function of libSBML:
make sure your libSBML version is >= 5.13." "$LINENO" 5
fi
done
#AC_SEARCH_LIBS([SBase_getPlugin], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
#AC_SEARCH_LIBS([SBMLExtensionRegistry_getRegisteredPackages], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
#AC_SEARCH_LIBS([GeneProductAssociation_setAssociation], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
......@@ -4077,7 +4239,7 @@ cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1
# report actual input values of CONFIG_FILES etc. instead of their
# values after options handling.
ac_log="
This file was extended by sybilSBML $as_me 2.0.8, which was
This file was extended by sybilSBML $as_me 3.0.0, which was
generated by GNU Autoconf 2.69. Invocation command line was
CONFIG_FILES = $CONFIG_FILES
......@@ -4124,13 +4286,13 @@ Usage: $0 [OPTION]... [TAG]...
Configuration files:
$config_files
Report bugs to <geliudie@uni-duesseldorf.de>."
Report bugs to <clausjonathan.fritzemeier@uni-duesseldorf.de>."
_ACEOF
cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1
ac_cs_config="`$as_echo "$ac_configure_args" | sed 's/^ //; s/[\\""\`\$]/\\\\&/g'`"
ac_cs_version="\\
sybilSBML config.status 2.0.8
sybilSBML config.status 3.0.0
configured by $0, generated by GNU Autoconf 2.69,
with options \\"\$ac_cs_config\\"
......
AC_INIT([sybilSBML], [2.0.8], [geliudie@uni-duesseldorf.de])
AC_INIT([sybilSBML], [3.0.0], [clausjonathan.fritzemeier@uni-duesseldorf.de])
dnl # --------------------------------------------------------------------
dnl # global (environment) variables
......@@ -236,6 +236,38 @@ AC_SEARCH_LIBS([readSBML], [sbml], ,
AC_MSG_ERROR([Could not link to libSBML:
use --with-sbml-lib or PKG_LIBS to specify the library path and the libraries to pass to the linker.]))
AC_CHECK_LIB([sbml], [readSBML], ,
AC_MSG_ERROR([Could not link to libSBML:
use --with-sbml-lib or PKG_LIBS to specify the library path and the libraries to pass to the linker.]))
AC_CHECK_HEADER([sbml/packages/fbc/common/FbcExtensionTypes.h], ,
AC_MSG_ERROR([Could not find specific FBC header of libSBML:
make sure your libSBML version is >= 5.13.]),
[#include <sbml/SBMLTypes.h>])
#AC_CHECK_LIB([sbml], [SBMLExtensionRegistry_getRegisteredPackages], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
AC_CHECK_FUNCS([SBase_getPlugin SBMLExtensionRegistry_getRegisteredPackages GeneProductAssociation_setAssociation FbcReactionPlugin_getLowerFluxBound], ,
AC_MSG_ERROR([Could not find specific FBC function of libSBML:
make sure your libSBML version is >= 5.13.]))
#AC_SEARCH_LIBS([SBase_getPlugin], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
#AC_SEARCH_LIBS([SBMLExtensionRegistry_getRegisteredPackages], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
#AC_SEARCH_LIBS([GeneProductAssociation_setAssociation], [sbml], ,
# AC_MSG_ERROR([Could not find specific FBC function of libSBML:
# make sure your libSBML version is >= 5.13.]))
dnl # --------------------------------------------------------------------
dnl # substitute src/Makevars
......
......@@ -4,7 +4,24 @@
\title{sybilSBML News}
\encoding{UTF-8}
\newcommand{\CRANpkg}{\href{http://CRAN.R-project.org/package=#1}{\pkg{#1}}}
\newcommand{\CRANpkg}{\href{https://cran.r-project.org/package=#1}{\pkg{#1}}}
% ---------------------------------------------------------------------------- %
\section{Changes in version 3.0.1 2016-12-16}{
\itemize{
\item sybilSBML now supports writing of SBML files.
\item The new FBC additional package for SBML is now fully integrated.
\item Urls in NEWS file are now in default style.
}
}
% ---------------------------------------------------------------------------- %
\section{Changes in version 2.0.11 2015-07-03}{
\itemize{
\item \code{gprRules}-Slot in \code{modelorg} has changed. Thus
\code{readSBMLmod} had to be updated.
}
}
% ---------------------------------------------------------------------------- %
\section{Changes in version 2.0.11 2015-07-03}{
......
### R code from vignette source 'sybilSBML.Rnw'
### Encoding: UTF-8
###################################################
### code chunk number 1: sybilSBML.Rnw:85-87 (eval = FALSE)
###################################################
## library(sybilSBML)
## model <- readSBMLmod("<model>.xml")
###################################################
### code chunk number 2: sybilSBML.Rnw:103-106
###################################################
library(sybilSBML)
mp <- system.file(package = "sybilSBML", "extdata")
ec_mod <- file.path(mp, "ecoli_core_model.xml")
###################################################
### code chunk number 3: sybilSBML.Rnw:109-110
###################################################
mod <- readSBMLmod(ec_mod, bndCond = FALSE)
###################################################
### code chunk number 4: sybilSBML.Rnw:123-124
###################################################
err <- validateSBMLdocument(ec_mod)
\documentclass[a4paper,headings=small]{scrartcl}
\usepackage[english]{babel}
\usepackage[T1]{fontenc}
\usepackage[utf8]{inputenc}
\usepackage{textcomp,lmodern}
\typearea[current]{last}
\usepackage{fixltx2e,mparhack,mathdots}
\usepackage{natbib}
%\usepackage{hyperref}
\usepackage{microtype}
\newcommand{\Comp}[1]{\texttt{#1}}
% bash command prompt
\DeclareRobustCommand{\PROMPTL}{\Comp{\$}}
% just a bash command
\DeclareRobustCommand{\COML}[1]{%
\small{\PROMPTL\Comp{ #1}}
}
% bash command with quote environment
\DeclareRobustCommand{\COMML}[1]{%
\begin{quote}%
\small{\PROMPTL\Comp{ #1}}
\end{quote}
}
\addtolength{\skip\footins}{0.5\baselineskip}
\usepackage{fnpos}
% \hypersetup{
% pdftitle = {sybilSBML -- Quick Start},
% pdfauthor = {Gabriel Gelius-Dietrich},
% pdfsubject = {SBML support for SyBiL},
% pdfkeywords = {SBML},
% pdfborder = {0 0 0},
% pdfhighlight = {/N}
% }
\newcommand{\pkg}[1]{\emph{#1}}
\newcommand{\CRANpkg}[1]{\href{http://CRAN.R-project.org/package=#1}{\pkg{#1}}}
%\newcommand{\pkgname}{\CRANpkg{sybilSBML}}
\newcommand{\pkgname}{\emph{sybilSBML}}
\newcommand{\prgname}[1]{\textsc{#1}}
\begin{document}
\title{sybilSBML -- Quick Start}
%\VignetteIndexEntry{Package sybilSBML -- Quick Start}
%\VignettePackage{sybilSBML}
\author{Gabriel Gelius-Dietrich}
\maketitle
\section{Introduction}
The package \pkgname{} is an addition to package
\pkg{sybil}\footnote{\texttt{http://CRAN.R-project.org/package=sybil}}
providing support for
metabolic networks written in SBML (Systems Biology Markup Language), in
particular those developed by Bernhard \O. Palsson's
lab\footnote{\texttt{http://gcrg.ucsd.edu/}} and those from the BiGG
database\footnote{\texttt{http://bigg.ucsd.edu/}} \citep{Schellenberger:2010fk}.
\nocite{Becker:2007uq,Schellenberger:2011fk}
\section{Installation}
The package \pkgname{} depends on a working installation of
LibSBML \citep{Bornstein:2008uq} available from the SBML
homepage\footnote{\texttt{http://www.sbml.org/}, libSBML version 5.6.0 or higher}
(in particular libraries and header files).
See \Comp{INSTALL} for installation instructions and platform specific details.
\section{Usage}
The package \pkgname{} provides the command \Comp{readSBMLmod()} which reads
SBML formated files and returns instances of class \Comp{modelorg}.
<<eval=FALSE>>=
library(sybilSBML)
model <- readSBMLmod("<model>.xml")
@
\section{Input files}
The function \Comp{readSBMLmod()} reads metabolic network models written in
SBML format (Systems Biology Markup Language). Among the models available in
this de-facto standard format are in particular those developed by
Bernhard \O. Palsson's lab.
The file \Comp{ecoli\_core\_model.xml} (in \Comp{extdata/}) contains an
exemplarily metabolic network written in SBML for the core energy metabolism
of \emph{E.~coli} \citep{Palsson:2006fk,Orth:2010fk}.
The exact location of the file can be retrieved with the \Comp{system.file()}
command:
<<>>=
library(sybilSBML)
mp <- system.file(package = "sybilSBML", "extdata")
ec_mod <- file.path(mp, "ecoli_core_model.xml")
@
The model can be read in by using the command \Comp{readSBMLmod()}:
<<print=true>>=
mod <- readSBMLmod(ec_mod, bndCond = FALSE)
@
The metabolite id's of the SBML files are written in the format
\Comp{M\_<metabolite abbreviation>\_<compartment abbreviation>}. The compartment
abbreviation is a one letter abbreviation, e.\,g. \Comp{c} for cytosol. All
metabolites outside the system boundary belong to compartment \Comp{b}. Those
metabolites are transported into or outside the system. As long as they are
mentioned, the network is closed. The function \Comp{readSBMLmod()} will remove
them in order to produce an open network.
\section{Validation of input files}
SBML files can be validated by using the command \Comp{validateSBMLdocument()}:
<<>>=
err <- validateSBMLdocument(ec_mod)
@
The variable \Comp{err} is of class \Comp{sbmlError}, storing error messages
generated by the validation procedure.
\bibliographystyle{abbrvnat}
\bibliography{sybilSBML}
\end{document}
File added
\name{getSBMLFbcversion}
\alias{getSBMLFbcversion}
\title{
Get SBML Version
}
\description{
Retrieve SBML FBC version of SBML file.
}
\usage{
getSBMLFbcversion(sbmlf)
}
\arguments{
\item{sbmlf}{
An object of class \code{\linkS4class{sbmlPtr}} as returned by
\code{\link{openSBMLfile}}. This is basically a pointer to a SBML document.
}
}
\value{
A single integer value containing the SBML FBC version of the SBML file.
}
\references{
Bornstein, B. J., Keating, S. M., Jouraku, A., and Hucka M. (2008)
LibSBML: An API Library for SBML. \emph{Bioinformatics} \bold{24},
880--881.
}
\author{
Gabriel Gelius-Dietrich <geliudie@uni-duesseldorf.de>
Maintainer: Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de>
}
\seealso{
\code{\link{openSBMLfile}}, \code{\linkS4class{sbmlPtr}}
}
\keyword{ IO }
\ No newline at end of file
\name{getSBMLmodAnnotation}
\alias{getSBMLmodAnnotation}
\title{
Get Model Annotation
}
\description{
Retrieve model annotation of a SBML model
}
\usage{
getSBMLmodAnnotation(sbmlm)
}
\arguments{
\item{sbmlm}{
An object of class \code{\linkS4class{sbmlPtr}} as returned by
\code{\link{getSBMLmodel}}. This is basically a pointer to a SBML model.
}
}
\value{
A single character string containing the model annotation of the SBML model.
}
\references{
Bornstein, B. J., Keating, S. M., Jouraku, A., and Hucka M. (2008)
LibSBML: An API Library for SBML. \emph{Bioinformatics} \bold{24},
880--881.
}
\author{
Gabriel Gelius-Dietrich <geliudie@uni-duesseldorf.de>
Maintainer: Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de>
}
\seealso{
\code{\link{getSBMLmodel}}, \code{\linkS4class{sbmlPtr}}
}
\keyword{ IO }
\ No newline at end of file
\name{getSBMLmodNotes}
\alias{getSBMLmodNotes}
\title{
Get Model Note
}
\description{
Retrieve model notes of a SBML model
}
\usage{
getSBMLmodNotes(sbmlm)
}
\arguments{
\item{sbmlm}{
An object of class \code{\linkS4class{sbmlPtr}} as returned by
\code{\link{getSBMLmodel}}. This is basically a pointer to a SBML model.
}
}
\value{
A single character string containing the model notes of the SBML model.
}
\references{
Bornstein, B. J., Keating, S. M., Jouraku, A., and Hucka M. (2008)
LibSBML: An API Library for SBML. \emph{Bioinformatics} \bold{24},
880--881.
}
\author{
Gabriel Gelius-Dietrich <geliudie@uni-duesseldorf.de>
Maintainer: Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de>
}
\seealso{
\code{\link{getSBMLmodel}}, \code{\linkS4class{sbmlPtr}}
}
\keyword{ IO }
\ No newline at end of file
\name{writeSBML}
\alias{writeSBML}
\encoding{utf8}
\title{Exports a Metabolic Network in SBML Format}
\description{
The function exports a metabolic network from S4 object of the class \code{\link{modelorg}} in SBML format. The function returns TRUE if the SBML file is successfully built.
}
\usage{
writeSBML(morg=NULL,level=2,version=4,fbcLevel=0,
filename="export.xml",
recoverExtMet=FALSE,
printNotes=TRUE,
printAnnos=TRUE,
validation=FALSE)
}
\arguments{
\item{morg}{
An S4 object of the class \code{\link[sybil]{modelorg}}.
}
\item{level}{
A single integer value containing the SBML level for the exporting SBML file. \cr
Default: \code{2}.
}
\item{version}{
A single integer value containing the SBML version for the exporting SBML file. \cr
Default: \code{4}.
}
\item{fbcLevel}{
A single integer value containing the fbc package version for the exporting SBML file. \cr
Default: \code{2}.
}
\item{filename}{
SBML filename for exporting the model.
Default: \code{"export.xml"}.
}
\item{recoverExtMet}{
Boolean: recover external metabolites and refer them to compartment \code{"BOUNDARY"}.\cr
Default: \code{FALSE}.
}
\item{printNotes}{
Boolean: print Notes from original SBML file .\cr
Default: \code{TRUE}.
}
\item{printAnnos}{
Boolean: print Annotations from original SBML file .\cr
Default: \code{TRUE}.
}
\item{validation}{
Boolean: print containing errors for xml file .\cr
Default: \code{TRUE}.
}
}
\details{
The library \code{libSBML} is used to export a \code{\link[sybil]{modelorg}}
to a SBML file.
}
\value{
A single boolean value for a successful export .
}
\references{
The BiGG database \url{http://bigg.ucsd.edu/}.
Bornstein, B. J., Keating, S. M., Jouraku, A., and Hucka M. (2008)
LibSBML: An API Library for SBML. \emph{Bioinformatics} \bold{24},
880--881.
Schellenberger, J., Park, J. O., Conrad, T. C., and Palsson, B. Ø., (2010)
BiGG: a Biochemical Genetic and Genomic knowledgebase of large scale metabolic
reconstructions. \emph{BMC Bioinformatics} \bold{11}, 213.
Becker, S. A., Feist, A. M., Mo, M. L., Hannum, G., Palsson, B. Ø. and
Herrgard, M. J. (2007) Quantitative prediction of cellular metabolism with
constraint-based models: the COBRA Toolbox. \emph{Nat Protoc} \bold{2},
727--738.
Schellenberger, J., Que, R., Fleming, R. M. T., Thiele, I., Orth, J. D.,
Feist, A. M., Zielinski, D. C., Bordbar, A., Lewis, N. E., Rahmanian, S.,
Kang, J., Hyduke, D. R. and Palsson, B. Ø. (2011) Quantitative prediction of
cellular metabolism with constraint-based models: the COBRA Toolbox v2.0.
\emph{Nat Protoc} \bold{6}, 1290--1307.
}
\author{
Gabriel Gelius-Dietrich <geliudie@uni-duesseldorf.de>
Maintainer: Claus Jonathan Fritzemeier <clausjonathan.fritzemeier@uni-duesseldorf.de>
}
\note{
The function \code{writeSBML} makes use of the library
\code{libSBML} (\url{http://www.sbml.org}).
}
\seealso{
\code{\link{readSBMLmod}}
}
\examples{
dir <- system.file(package = "sybilSBML", "extdata")
file <- file.path(dir, "ecoli_core_model.xml")
mod <- readSBMLmod(file, bndCond = FALSE)
writeSBML(mod,level=3,version=1,fbcLevel=2)
}
\keyword{ IO }
......@@ -45,6 +45,8 @@ static const R_CallMethodDef callMethods[] = {
{"getSBMLmodel", (DL_FUNC) &getSBMLmodel, 2},
{"getSBMLmodId", (DL_FUNC) &getSBMLmodId, 1},
{"getSBMLmodName", (DL_FUNC) &getSBMLmodName, 1},
{"getSBMLmodNotes", (DL_FUNC) &getSBMLmodNotes, 1},
{"getSBMLmodAnnotation", (DL_FUNC) &getSBMLmodAnnotation, 1},
{"getSBMLnumCompart", (DL_FUNC) &getSBMLnumCompart, 1},
{"getSBMLnumSpecies", (DL_FUNC) &getSBMLnumSpecies, 1},
{"getSBMLnumReactions", (DL_FUNC) &getSBMLnumReactions, 1},
......@@ -52,6 +54,8 @@ static const R_CallMethodDef callMethods[] = {
{"getSBMLCompartList", (DL_FUNC) &getSBMLCompartList, 1},
{"getSBMLSpeciesList", (DL_FUNC) &getSBMLSpeciesList, 1},
{"getSBMLReactionsList", (DL_FUNC) &getSBMLReactionsList, 1},
{"exportSBML", (DL_FUNC) &exportSBML, 33},
{"getSBMLFbcversion", (DL_FUNC) &getSBMLFbcversion, 1},
{NULL, NULL, 0}
};
......@@ -62,5 +66,3 @@ void R_init_sybilSBML(DllInfo *info) {
R_registerRoutines(info, NULL, callMethods, NULL, NULL);
R_useDynamicSymbols(info, FALSE);
}
\ No newline at end of file
This diff is collapsed.
......@@ -63,6 +63,9 @@ SEXP getSBMLlevel(SEXP sbmldoc);
/* get sbml document version */
SEXP getSBMLversion(SEXP sbmldoc);
/* get sbml document FBC version */
SEXP getSBMLFbcversion(SEXP sbmldoc);
/* validate SBML document */
SEXP validateDocument(SEXP sbmldoc);
......@@ -78,6 +81,12 @@ SEXP getSBMLmodId(SEXP sbmlmod);
/* get model name */
SEXP getSBMLmodName(SEXP sbmlmod);
/* get model notes */
SEXP getSBMLmodNotes(SEXP sbmlmod);
/* get model annotation */
SEXP getSBMLmodAnnotation(SEXP sbmlmod);
/* get number of compartments */
SEXP getSBMLnumCompart(SEXP sbmlmod);
......@@ -98,3 +107,6 @@ SEXP getSBMLSpeciesList(SEXP sbmlmod);
/* get list of reactions */
SEXP getSBMLReactionsList(SEXP sbmlmod);
/* export Modelorg to SBML*/
SEXP exportSBML (SEXP version, SEXP level,SEXP FbcLevel, SEXP filename,SEXP sybil_max, SEXP mod_desc, SEXP mod_name, SEXP mod_compart, SEXP met_id, SEXP met_name, SEXP met_comp, SEXP met_form,SEXP met_charge, SEXP react_id, SEXP react_name, SEXP react_rev, SEXP lowbnd, SEXP uppbnd, SEXP obj_coef, SEXP subSys, SEXP gpr, SEXP SMatrix, SEXP mod_notes, SEXP mod_anno, SEXP com_notes , SEXP com_anno, SEXP met_notes, SEXP met_anno, SEXP met_bnd , SEXP react_notes, SEXP react_anno, SEXP ex_react, SEXP allgenes);
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment