diff --git a/DESCRIPTION b/DESCRIPTION index 7b79b60fcf2144cc4a16e486a31b14acc79c389b..6798ad6118f493a90e74bed390e9ce0e1d9d3a4e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,8 +1,8 @@ Package: sybilSBML Type: Package Title: SBML Integration in Package 'Sybil' -Version: 3.0.6 -Date: 2019-07-03 +Version: 3.0.7 +Date: 2019-08-02 Authors@R: c(person("Mayo", "Roettger", role = "cre", email = "mayo.roettger@hhu.de"), person("Gabriel", "Gelius-Dietrich", role = c("aut", "ctb")), person(c("C.", "Jonathan"), "Fritzemeier", role = "ctb", email = "clausjonathan.fritzemeier@uni-duesseldorf.de"), @@ -17,7 +17,7 @@ License: GPL-3 | file LICENSE LazyLoad: yes Collate: generics.R sbmlPtrClass.R sbmlErrorClass.R sybilSBML.R uglyHack.R readSBMLmod.R zzz.R -Packaged: 2019-07-03 15:45:00 UTC; mayo +Packaged: 2019-08-02 15:05:20 UTC; mayo Author: Mayo Roettger [cre], Gabriel Gelius-Dietrich [aut, ctb], C. Jonathan Fritzemeier [ctb], diff --git a/NAMESPACE b/NAMESPACE index ef1a335a79643feaf6af3485646e34b13d8d8eea..a6c848779df60cc18084a98eef945d78fa338a1f 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -52,5 +52,7 @@ readSBMLmod, writeSBML, getSBMLFbcversion, getSBMLmodNotes, -getSBMLmodAnnotation +getSBMLmodAnnotation, +isAvailableFbcPlugin, +isAvailableGroupsPlugin ) diff --git a/R/readSBMLmod.R b/R/readSBMLmod.R index c407a8897b8fcff8dce0eaeb58751ca407a0f5ea..5575ee0da9c14f53c782ea73a0be53677864468d 100644 --- a/R/readSBMLmod.R +++ b/R/readSBMLmod.R @@ -57,12 +57,13 @@ on.exit(expr = { } ) #------------------------------------------------------------------------------# -# open the model file +# Does the model file exist? if ( file.exists(filename) == FALSE ) { stop("failed to open file ", sQuote(filename)) } +# set description to filename, if not set if (missing(description)) { mdesc <- filename } @@ -96,6 +97,7 @@ entryforS <- function(X) { CURR_MET <- character(n) # metabolites in X t <- 0 + # over all metabolite IDs: for (i in seq(along = X[["species"]])) { t <- t + 1 @@ -104,21 +106,23 @@ entryforS <- function(X) { # The metabolite id's are removed from the metabolites list, # but not from the reactions list. - CURR_MET[t] <- X[["species"]][i] + CURR_MET[t] <- X[["species"]][i] # get current metabolite ID + if (isTRUE(mergeMet)) { + # find out, if the current metabolite is already in the list and remember matching position in CURR_MET vector: met_indCURR <- match(CURR_MET[t], CURR_MET[-t]) } else { met_indCURR <- NA } - if (is.na(met_indCURR)) { + if (is.na(met_indCURR)) {# if we don't have to merge metabolite --> check this!#### sj[t] <- match(X[["species"]][i], met_id_tmp) # the row number s_ji[t] <- X[["stoichiometry"]][i] - remMet[t] <- ifelse(is.na(sj[t]), FALSE, TRUE) + remMet[t] <- ifelse(is.na(sj[t]), FALSE, TRUE) # } - else { + else {# we have to merge metabolite --> check this!#### remMet[t] <- FALSE s_ji[met_indCURR] <- s_ji[met_indCURR] + X[["stoichiometry"]][i] msg <- paste("reaction no.", i, dQuote(react_id_tmp[i]), @@ -211,6 +215,8 @@ formatSBMLid <- function(idstr) { #------------------------------------------------------------------------------# # parse the notes field of the reactions +# (notes is a character string) +# extract gpr rules and subsystem from notes #------------------------------------------------------------------------------# parseNotesReact <- function(notes) { @@ -226,35 +232,49 @@ parseNotesReact <- function(notes) { #split <- "\n" fields <- strsplit(notes, split, fixed = TRUE) - # print(fields) + # print(fields) + # fields now contains a list in which each item is a vector with the strings separated by the <p> or <html:p> respectively + # we only have one element in the list here. + + # extract the actual notes between the opening and closing tags: start_tag <- paste("<", tag, ">", sep = "") end_tag <- paste("</", tag, ">", sep = "") regex <- paste("^(?:[\\t]*\\Q", start_tag, "\\E)?", "(.*)", "\\Q", end_tag, "\\E", "(?s).*$", sep = "") -# regex <- paste("(.*)", end_tag, "(?s).*$", sep = "") + #regex <- paste("(.*)", end_tag, "(?s).*$", sep = "") #print(regex) fields_str <- sub(regex, "\\1", fields[[1]], perl = TRUE) #print(fields_str) + # fields_str should now contain a vector of the actual notes without surrounding tags - subSyst <- "" - gpr <- "" + + # extract gpr rule (genes and rules) and subsystem from notes: + subSyst <- ""# no sub system + gpr <- ""# no gene to protein to reaction interaction gene_rule <- NA for (j in 1:length(fields_str)) { + # Do we have a "GENE_ASSOCIATION" or "GENE ASSOCIATION" or GENEASSOCIATION? if (grepl("GENE[_ ]?ASSOCIATION", fields_str[j])) { #if (charmatch("GENE", fields_str[j], nomatch = -1) != -1) { - gpr <- sub("GENE[_ ]?ASSOCIATION: *", "", fields_str[j]) - gene_rule <- sybil:::.parseBoolean(gpr) + gpr <- sub("GENE[_ ]?ASSOCIATION: *", "", fields_str[j])# delete the text, remaining gpr + + # get the unique gene names and the rule with the x[gene number] codes: + gene_rule <- sybil:::.parseBoolean(gpr)# parse gene rule #print(gene_rule) - + }#Ardalan Habil + # Or do we have a "GPR_ASSOCIATION" or "GPR ASSOCIATION" or GPRASSOCIATION? else if (grepl("GPR[_ ]?ASSOCIATION", fields_str[j])) { gpr <- sub("GPR[_ ]?ASSOCIATION: *", "", fields_str[j]) + # get the unique gene names and the rule with the x[gene number] codes: gene_rule <- sybil:::.parseBoolean(gpr) - } - + } + + # Do we have a "SUBSYSTEM"? if (charmatch("SUBSYSTEM", fields_str[j], nomatch = -1) != -1) { + # remove SUBSYSTEM with trailing trailing spaces, then remove the S_ at the beginning, then exchange all _ by spaces: subSyst <- sub("SUBSYSTEM: *", "", fields_str[j]) subSyst <- sub("^S_", "", subSyst, perl = TRUE) subSyst <- gsub("[_]+", " ", subSyst) @@ -267,7 +287,8 @@ parseNotesReact <- function(notes) { if (!is.list(gene_rule)) { gene_rule <- sybil:::.parseBoolean("") } - + + # return sub system, genes, and rules: return(list(sub_system = subSyst, genes = gene_rule$gene, rules = gene_rule$rule, gpr = gpr)) } @@ -289,6 +310,16 @@ sbmldoc <- openSBMLfile(filename) message("OK") +# warning, if FBC plugin is missing: +if (isAvailableFbcPlugin() == FALSE) { + warning("Missing FBC-plugin for libSBML. FBC constraints will be ignored.") +} + +# warning, if Groups plugin is missing: +if (isAvailableGroupsPlugin() == FALSE) { + warning("Missing Groups-plugin for libSBML. Groups will be ignored.") +} + # warning if new Version/Level/ SBMLlevel<- getSBMLlevel(sbmldoc) SBMLversion<- getSBMLversion(sbmldoc) @@ -298,6 +329,7 @@ if(SBMLlevel == 3 && SBMLversion > 1) if (FBCversion > 2) warning(paste("No support for Fbc Version ",FBCversion)) + #------------------------------------------------------------------------------# # check the model # #------------------------------------------------------------------------------# @@ -442,24 +474,24 @@ if (is.null(metabolitesList)) { } missingId(metabolitesList) -metSpIds <- metabolitesList[["id"]] +metSpIds <- metabolitesList[["id"]]# Metabolites IDs #nummet <- getSBMLnumSpecies(sbmlmod) if (isTRUE(bndCond)) { - metSpBnd <- metabolitesList[["boundaryCondition"]] - met_id_pos <- !metSpBnd + metSpBnd <- metabolitesList[["boundaryCondition"]]# TRUE for external, FALSE for internal metabolites + met_id_pos <- !metSpBnd# TRUE for internal metabolites } else { # regular expression to identify external metabolites extMetRegEx <- paste("_", extMetFlag, "$", sep = "") - met_id_pos <- grep(extMetRegEx, metSpIds, invert = TRUE) + met_id_pos <- grep(extMetRegEx, metSpIds, invert = TRUE)# positions of internal metabolites } -met_id_tmp <- metSpIds[met_id_pos] +met_id_tmp <- metSpIds[met_id_pos]# IDs of internal metabolites # number of metabolites -nummet <- length(met_id_tmp) +nummet <- length(met_id_tmp)# No. internal metabolites #------------------------------------------------------------------------------# @@ -515,33 +547,35 @@ for (i in 1 : numreact) { # Notes und Annotation can be null ( @Ardalan Habil) if(!is.null( reactionsList[["notes"]])) - if (nchar(notes) > 0) { + if (nchar(notes) > 0) { - hasNotes <- TRUE - notes_field <- parseNotesReact(notes) - #print(notes_field) - subSys[i] <- notes_field$sub_system # the reaction's sub system: glykolysis, TCA, ... - genes[[i]] <- notes_field$genes # list of genes - rules[i] <- notes_field$rules # rules - gpr[i] <- notes_field$gpr # original gpr association - #allGenes <- c(allGenes, genes[[i]]) + hasNotes <- TRUE + notes_field <- parseNotesReact(notes) + #print(notes_field) + subSys[i] <- notes_field$sub_system # the reaction's sub system: glykolysis, TCA, ... + genes[[i]] <- notes_field$genes # list of genes + rules[i] <- notes_field$rules # rules + gpr[i] <- notes_field$gpr # original gpr association + #allGenes <- c(allGenes, genes[[i]]) - } - else { - if(!is.null( reactionsList[["annotation"]])) - if (nchar(annot) > 0) { - hasAnnot <- TRUE - pn <- regexpr("Pathway Name: [^<]+", annot, perl = TRUE) - subSys[i] <- substr(annot, (pn+14), pn + ((attr(pn, "match.length"))-1)) + } + else { + if(!is.null( reactionsList[["annotation"]])) + if (nchar(annot) > 0) { + hasAnnot <- TRUE + pn <- regexpr("Pathway Name: [^<]+", annot, perl = TRUE) + subSys[i] <- substr(annot, (pn+14), pn + ((attr(pn, "match.length"))-1)) } } - - - + + + + # get flux balance constraints, if fbcgprRules not null fbcgene_rule <- NA if ( !is.null(fbcgprRules)) { + # get the unique gene names and the rule with the x[gene number] codes: fbcgene_rule<- sybil:::.parseBoolean(fbcgprRules[i]) genes[[i]] <- fbcgene_rule$gene # list of genes @@ -549,12 +583,15 @@ for (i in 1 : numreact) { gpr[i] <- fbcgprRules[i] } + + # Check here if reactants and products lists exist, same for the stoichiometry slot # Entries for S -- the reactants - S_tmp <- entryforS(reactionsList[["reactants"]][[i]]) + S_tmp <- entryforS(reactionsList[["reactants"]][[i]])# todo: have to give i and met_id_tmp as argument, right now they are global (confusing) #print(S_tmp) if (is.list(S_tmp) == TRUE) { + # set stoichiometric matrix, values are set negative (reactants) St[S_tmp$sj, i] <- (S_tmp$s_ji * -1) #St[S_tmp$sj, S_tmp$si] <- (S_tmp$s_ji * -1) } @@ -638,10 +675,10 @@ for (i in 1 : numreact) { } } #FBC Objective @Ardalan Habil - if(!is.null(fbcObjectives)) - { + if(!is.null(fbcObjectives)) + { ocof[i]<-as.numeric(fbcObjectives[i]) - } + } } @@ -649,6 +686,8 @@ for (i in 1 : numreact) { # get subsystem properties from the sbml groups plugin subSysGroups <- getSBMLGroupsList(sbmlmod) + + # ---------------------------------------------------------------------------- # # search for unused metabolites and unused reactions @@ -699,6 +738,7 @@ if ( any(SKIP_REACTION == FALSE) ) { warning(msg, call. = FALSE) } +# if we do not want to remove, mark them as to skip if (!isTRUE(remUnusedMetReact)) { SKIP_METABOLITE[!SKIP_METABOLITE] <- TRUE SKIP_REACTION[!SKIP_REACTION] <- TRUE @@ -867,6 +907,7 @@ if (isTRUE(deadEndMet)) { # ---------------------------------------------------------------------------- # # S +# only keep metabolites and reactions where SKIP mark is TRUE, remove the rest St <- St[SKIP_METABOLITE, , drop = FALSE] St <- St[ , SKIP_REACTION, drop = FALSE] @@ -925,33 +966,36 @@ if (isTRUE(ignoreNoAn)) { sybil::subSys(mod) <- Matrix::Matrix(FALSE, nrow = numreact, ncol = 1, sparse = TRUE) } else { - subSys <- subSys[SKIP_REACTION] genes <- genes[SKIP_REACTION] rules <- rules[SKIP_REACTION] gpr <- gpr[SKIP_REACTION] - + + # if there were fbcgprRules or notes with gpr rules, + # create reaction x nGene matrix, with TRUE for respective genes for each reaction if (isTRUE(hasNotes) || !is.null(fbcgprRules) ) { message("GPR mapping ... ", appendLF = FALSE) + # Vector with all gene names != "": #allGenes <- unique(allGenes) #allGenesTMP <- unique(allGenes) allGenesTMP <- unique(unlist(genes)) temp <- nchar(allGenesTMP) allGenes <- allGenesTMP[which(temp != 0)] - rxnGeneMat <- Matrix::Matrix(FALSE, nrow = numreact, ncol = length(allGenes), sparse = TRUE) for (i in 1 : numreact) { - + # if genes list element i has only 1 element and that element is not equal "" if ( (length(genes[[i]] == 1)) && (genes[[i]] != "") ) { - geneInd <- match(genes[[i]], allGenes) + geneInd <- match(genes[[i]], allGenes)# find gene in allGenes + # Mark which genes are used in reaction with TRUE rxnGeneMat[i, geneInd] <- TRUE + # exchange x(j) with x[j] for each gene index: for (j in 1 : length(geneInd)) { pat <- paste("x(", j, ")", sep = "") repl <- paste("x[", geneInd[j], "]", sep = "") @@ -961,6 +1005,7 @@ else { } } + # sybil::genes(mod) <- genes sybil::gpr(mod) <- gpr sybil::allGenes(mod) <- allGenes @@ -979,13 +1024,15 @@ else { message("OK") } - else { + else {# no notes and no fbcgprRules: sybil::rxnGeneMat(mod) <- Matrix::Matrix(NA, nrow = 0, ncol = 0) if (isTRUE(hasAnnot)) { + # then we extracted the subsystem from annotation, so set it: #subSys(sbml) <- subSys sybil::subSys(mod) <- sybil:::.prepareSubSysMatrix(subSys, numreact) } else { + # No subsystems: sybil::subSys(mod) <- Matrix::Matrix(FALSE, nrow = numreact, ncol = 1, @@ -1050,6 +1097,7 @@ if(newSybil) #------------------------------------------------------------------------------# if(!is.null(subSysGroups)){ + # sub system groups for each reaction from subSysGroups: subSysMat <- Matrix::Matrix(FALSE, nrow = numreact, ncol = length(subSysGroups), sparse = TRUE) colnames(subSysMat) <- names(subSysGroups) @@ -1072,6 +1120,7 @@ modanno<-getSBMLmodAnnotation(sbmlmod) modnotes<-getSBMLmodNotes(sbmlmod) if(newSybil) { + # set model annotation and notes: 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 @@ -1082,6 +1131,7 @@ if(newSybil) #------------------------------------------------------------------------------# # compartments Attr @Ardalan # #------------------------------------------------------------------------------# +# set comp_attr slot for model with 'annotation' and 'notes' from values in compartmentsList: # 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) @@ -1165,29 +1215,38 @@ 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} + { + sybil::met_attr(mod)[['chemicalFormula']]<-metformula + } else{ if(length(metformulanote)==nummet) - { if(max(nchar(metformulanote)) >0) - sybil::met_attr(mod)[['chemicalFormula']]<-metformulanote + { + 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} + { + sybil::met_attr(mod)[['charge']]<-metcharge + } else{ if( length(metchargenote)==nummet) - { if(max(nchar(metchargenote)) >0) - sybil::met_attr(mod)[['charge']]<-metchargenote + { + 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 + 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 + if( !is.null(metBnd) && length(metBnd)==nummet && !all(metBnd == FALSE) ) + sybil::met_attr(mod)[['boundaryCondition']]<-metBnd } diff --git a/R/sbmlPtrClass.R b/R/sbmlPtrClass.R index 81931e85ecc405620c56604e177071262008c4e9..70e2b91833243f15717d279c27fae8c767da833a 100644 --- a/R/sbmlPtrClass.R +++ b/R/sbmlPtrClass.R @@ -60,7 +60,7 @@ setMethod(f = "initialize", ) -# contructor for pointers to sbml documents +# constructor for pointers to sbml documents sbmlDocPointer <- function(pointer) { if (is(pointer, "sbml_doc_ptr")) { diff --git a/R/sybilSBML.R b/R/sybilSBML.R index 0b6dc6da035b8da1532dc8e43ad19e22e808ed81..12c0a0a02603ba1224292db9a8c883b26b922b06 100644 --- a/R/sybilSBML.R +++ b/R/sybilSBML.R @@ -346,6 +346,16 @@ writeSBML<- function(morg=NULL,level=2,version=4,fbcLevel=0,filename="export.xml stop("morg has to be of class modelorg\n") } + # warning, if FBC plugin is missing: + if (isAvailableFbcPlugin() == FALSE) { + warning("Missing FBC-plugin for libSBML. No SBML output will be written.") + } + + # warning, if Groups plugin is missing: + if (isAvailableGroupsPlugin() == FALSE) { + warning("Missing Groups-plugin for libSBML. No SBML output will be written.") + } + ###right if(level==1) { @@ -643,3 +653,27 @@ writeSBML<- function(morg=NULL,level=2,version=4,fbcLevel=0,filename="export.xml else message(paste("Could not write file ",filename,"\n",sep=""), appendLF = FALSE); return (success) } + + + +#------------------------------------------------------------------------------# + +isAvailableFbcPlugin <- function() { + + avail <- .Call("isAvailableFbcPlugin", PACKAGE = "sybilSBML" + ) + + return(avail) +} + + + +#------------------------------------------------------------------------------# + +isAvailableGroupsPlugin <- function() { + + avail <- .Call("isAvailableGroupsPlugin", PACKAGE = "sybilSBML" + ) + + return(avail) +} diff --git a/build/vignette.rds b/build/vignette.rds index 217b014b3aaa3d2181c33fc96a7045116045540b..1ff49c7676081ca7e745c1f7bfd0056761ffa96c 100644 Binary files a/build/vignette.rds and b/build/vignette.rds differ diff --git a/configure b/configure index a6d881cdadb42faedd69b4cfacb9614d78e43886..331c6a410c86fb2487eb9a35b57d79fa235d8f73 100755 --- a/configure +++ b/configure @@ -1,6 +1,6 @@ #! /bin/sh # Guess values for system-dependent variables and create Makefiles. -# Generated by GNU Autoconf 2.69 for sybilSBML 3.0.6. +# Generated by GNU Autoconf 2.69 for sybilSBML 3.0.7. # # Report bugs to <mayo.roettger@hhu.de>. # @@ -580,8 +580,8 @@ MAKEFLAGS= # Identity of this package. PACKAGE_NAME='sybilSBML' PACKAGE_TARNAME='sybilsbml' -PACKAGE_VERSION='3.0.6' -PACKAGE_STRING='sybilSBML 3.0.6' +PACKAGE_VERSION='3.0.7' +PACKAGE_STRING='sybilSBML 3.0.7' PACKAGE_BUGREPORT='mayo.roettger@hhu.de' PACKAGE_URL='' @@ -1241,7 +1241,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 3.0.6 to adapt to many kinds of systems. +\`configure' configures sybilSBML 3.0.7 to adapt to many kinds of systems. Usage: $0 [OPTION]... [VAR=VALUE]... @@ -1303,7 +1303,7 @@ fi if test -n "$ac_init_help"; then case $ac_init_help in - short | recursive ) echo "Configuration of sybilSBML 3.0.6:";; + short | recursive ) echo "Configuration of sybilSBML 3.0.7:";; esac cat <<\_ACEOF @@ -1390,7 +1390,7 @@ fi test -n "$ac_init_help" && exit $ac_status if $ac_init_version; then cat <<\_ACEOF -sybilSBML configure 3.0.6 +sybilSBML configure 3.0.7 generated by GNU Autoconf 2.69 Copyright (C) 2012 Free Software Foundation, Inc. @@ -1759,7 +1759,7 @@ 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 3.0.6, which was +It was created by sybilSBML $as_me 3.0.7, which was generated by GNU Autoconf 2.69. Invocation command line was $ $0 $@ @@ -3050,6 +3050,8 @@ ac_compiler_gnu=$ac_cv_c_compiler_gnu +ac_config_headers="$ac_config_headers src/config.h" + @@ -3655,26 +3657,44 @@ else 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> +for ac_header in sbml/packages/fbc/common/FbcExtensionTypes.h +do : + 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 : + cat >>confdefs.h <<_ACEOF +#define HAVE_SBML_PACKAGES_FBC_COMMON_FBCEXTENSIONTYPES_H 1 +_ACEOF else - as_fn_error $? "Could not find specific FBC header of libSBML: - make sure your libSBML version is >= 5.16 and including the FBC package." "$LINENO" 5 + { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Could not find specific FBC header of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package." >&5 +$as_echo "$as_me: WARNING: Could not find specific FBC header of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package." >&2;} fi +done -ac_fn_c_check_header_compile "$LINENO" "sbml/packages/groups/common/GroupsExtensionTypes.h" "ac_cv_header_sbml_packages_groups_common_GroupsExtensionTypes_h" "#include <sbml/SBMLTypes.h> +for ac_header in sbml/packages/groups/common/GroupsExtensionTypes.h +do : + ac_fn_c_check_header_compile "$LINENO" "sbml/packages/groups/common/GroupsExtensionTypes.h" "ac_cv_header_sbml_packages_groups_common_GroupsExtensionTypes_h" "#include <sbml/SBMLTypes.h> " if test "x$ac_cv_header_sbml_packages_groups_common_GroupsExtensionTypes_h" = xyes; then : + cat >>confdefs.h <<_ACEOF +#define HAVE_SBML_PACKAGES_GROUPS_COMMON_GROUPSEXTENSIONTYPES_H 1 +_ACEOF + +$as_echo "#define HAVE_GROUPS_PLUGIN 1" >>confdefs.h else - as_fn_error $? "Could not find specific groups package header of libSBML: - make sure your libSBML version is >= 5.16 and including the groups package." "$LINENO" 5 + { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Could not find specific groups package header of libSBML: + make sure your libSBML version is >= 5.18 and including the groups package." >&5 +$as_echo "$as_me: WARNING: Could not find specific groups package header of libSBML: + make sure your libSBML version is >= 5.18 and including the groups package." >&2;} fi +done #AC_CHECK_LIB([sbml], [SBMLExtensionRegistry_getRegisteredPackages], , @@ -3690,9 +3710,13 @@ if eval test \"x\$"$as_ac_var"\" = x"yes"; then : #define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1 _ACEOF +$as_echo "#define HAVE_FBC_PLUGIN 1" >>confdefs.h + else - as_fn_error $? "Could not find specific FBC function of libSBML: - make sure your libSBML version is >= 5.16 and including the FBC package." "$LINENO" 5 + { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Could not find specific FBC function of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package." >&5 +$as_echo "$as_me: WARNING: Could not find specific FBC function of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package." >&2;} fi done @@ -3809,43 +3833,7 @@ test "x$prefix" = xNONE && prefix=$ac_default_prefix # Let make expand exec_prefix. test "x$exec_prefix" = xNONE && exec_prefix='${prefix}' -# Transform confdefs.h into DEFS. -# Protect against shell expansion while executing Makefile rules. -# Protect against Makefile macro expansion. -# -# If the first sed substitution is executed (which looks for macros that -# take arguments), then branch to the quote section. Otherwise, -# look for a macro that doesn't take arguments. -ac_script=' -:mline -/\\$/{ - N - s,\\\n,, - b mline -} -t clear -:clear -s/^[ ]*#[ ]*define[ ][ ]*\([^ (][^ (]*([^)]*)\)[ ]*\(.*\)/-D\1=\2/g -t quote -s/^[ ]*#[ ]*define[ ][ ]*\([^ ][^ ]*\)[ ]*\(.*\)/-D\1=\2/g -t quote -b any -:quote -s/[ `~#$^&*(){}\\|;'\''"<>?]/\\&/g -s/\[/\\&/g -s/\]/\\&/g -s/\$/$$/g -H -:any -${ - g - s/^\n// - s/\n/ /g - p -} -' -DEFS=`sed -n "$ac_script" confdefs.h` - +DEFS=-DHAVE_CONFIG_H ac_libobjs= ac_ltlibobjs= @@ -4261,7 +4249,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 3.0.6, which was +This file was extended by sybilSBML $as_me 3.0.7, which was generated by GNU Autoconf 2.69. Invocation command line was CONFIG_FILES = $CONFIG_FILES @@ -4279,11 +4267,15 @@ case $ac_config_files in *" "*) set x $ac_config_files; shift; ac_config_files=$*;; esac +case $ac_config_headers in *" +"*) set x $ac_config_headers; shift; ac_config_headers=$*;; +esac cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # Files that config.status was made for. config_files="$ac_config_files" +config_headers="$ac_config_headers" _ACEOF @@ -4304,17 +4296,22 @@ Usage: $0 [OPTION]... [TAG]... --recheck update $as_me by reconfiguring in the same conditions --file=FILE[:TEMPLATE] instantiate the configuration file FILE + --header=FILE[:TEMPLATE] + instantiate the configuration header FILE Configuration files: $config_files +Configuration headers: +$config_headers + Report bugs to <mayo.roettger@hhu.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 3.0.6 +sybilSBML config.status 3.0.7 configured by $0, generated by GNU Autoconf 2.69, with options \\"\$ac_cs_config\\" @@ -4368,7 +4365,18 @@ do esac as_fn_append CONFIG_FILES " '$ac_optarg'" ac_need_defaults=false;; - --he | --h | --help | --hel | -h ) + --header | --heade | --head | --hea ) + $ac_shift + case $ac_optarg in + *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; + esac + as_fn_append CONFIG_HEADERS " '$ac_optarg'" + ac_need_defaults=false;; + --he | --h) + # Conflict between --help and --header + as_fn_error $? "ambiguous option: \`$1' +Try \`$0 --help' for more information.";; + --help | --hel | -h ) $as_echo "$ac_cs_usage"; exit ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil | --si | --s) @@ -4424,6 +4432,7 @@ cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 for ac_config_target in $ac_config_targets do case $ac_config_target in + "src/config.h") CONFIG_HEADERS="$CONFIG_HEADERS src/config.h" ;; "src/Makevars") CONFIG_FILES="$CONFIG_FILES src/Makevars" ;; *) as_fn_error $? "invalid argument: \`$ac_config_target'" "$LINENO" 5;; @@ -4437,6 +4446,7 @@ done # bizarre bug on SunOS 4.1.3. if $ac_need_defaults; then test "${CONFIG_FILES+set}" = set || CONFIG_FILES=$config_files + test "${CONFIG_HEADERS+set}" = set || CONFIG_HEADERS=$config_headers fi # Have a temporary directory for convenience. Make it in the build tree @@ -4624,8 +4634,116 @@ fi cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 fi # test -n "$CONFIG_FILES" +# Set up the scripts for CONFIG_HEADERS section. +# No need to generate them if there are no CONFIG_HEADERS. +# This happens for instance with `./config.status Makefile'. +if test -n "$CONFIG_HEADERS"; then +cat >"$ac_tmp/defines.awk" <<\_ACAWK || +BEGIN { +_ACEOF + +# Transform confdefs.h into an awk script `defines.awk', embedded as +# here-document in config.status, that substitutes the proper values into +# config.h.in to produce config.h. + +# Create a delimiter string that does not exist in confdefs.h, to ease +# handling of long lines. +ac_delim='%!_!# ' +for ac_last_try in false false :; do + ac_tt=`sed -n "/$ac_delim/p" confdefs.h` + if test -z "$ac_tt"; then + break + elif $ac_last_try; then + as_fn_error $? "could not make $CONFIG_HEADERS" "$LINENO" 5 + else + ac_delim="$ac_delim!$ac_delim _$ac_delim!! " + fi +done + +# For the awk script, D is an array of macro values keyed by name, +# likewise P contains macro parameters if any. Preserve backslash +# newline sequences. + +ac_word_re=[_$as_cr_Letters][_$as_cr_alnum]* +sed -n ' +s/.\{148\}/&'"$ac_delim"'/g +t rset +:rset +s/^[ ]*#[ ]*define[ ][ ]*/ / +t def +d +:def +s/\\$// +t bsnl +s/["\\]/\\&/g +s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ +D["\1"]=" \3"/p +s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2"/p +d +:bsnl +s/["\\]/\\&/g +s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ +D["\1"]=" \3\\\\\\n"\\/p +t cont +s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2\\\\\\n"\\/p +t cont +d +:cont +n +s/.\{148\}/&'"$ac_delim"'/g +t clear +:clear +s/\\$// +t bsnlc +s/["\\]/\\&/g; s/^/"/; s/$/"/p +d +:bsnlc +s/["\\]/\\&/g; s/^/"/; s/$/\\\\\\n"\\/p +b cont +' <confdefs.h | sed ' +s/'"$ac_delim"'/"\\\ +"/g' >>$CONFIG_STATUS || ac_write_fail=1 + +cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 + for (key in D) D_is_set[key] = 1 + FS = "" +} +/^[\t ]*#[\t ]*(define|undef)[\t ]+$ac_word_re([\t (]|\$)/ { + line = \$ 0 + split(line, arg, " ") + if (arg[1] == "#") { + defundef = arg[2] + mac1 = arg[3] + } else { + defundef = substr(arg[1], 2) + mac1 = arg[2] + } + split(mac1, mac2, "(") #) + macro = mac2[1] + prefix = substr(line, 1, index(line, defundef) - 1) + if (D_is_set[macro]) { + # Preserve the white space surrounding the "#". + print prefix "define", macro P[macro] D[macro] + next + } else { + # Replace #undef with comments. This is necessary, for example, + # in the case of _POSIX_SOURCE, which is predefined and required + # on some systems where configure will not decide to define it. + if (defundef == "undef") { + print "/*", prefix defundef, macro, "*/" + next + } + } +} +{ print } +_ACAWK +_ACEOF +cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 + as_fn_error $? "could not setup config headers machinery" "$LINENO" 5 +fi # test -n "$CONFIG_HEADERS" + -eval set X " :F $CONFIG_FILES " +eval set X " :F $CONFIG_FILES :H $CONFIG_HEADERS " shift for ac_tag do @@ -4833,7 +4951,30 @@ which seems to be undefined. Please make sure it is defined" >&2;} esac \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; - + :H) + # + # CONFIG_HEADER + # + if test x"$ac_file" != x-; then + { + $as_echo "/* $configure_input */" \ + && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" + } >"$ac_tmp/config.h" \ + || as_fn_error $? "could not create $ac_file" "$LINENO" 5 + if diff "$ac_file" "$ac_tmp/config.h" >/dev/null 2>&1; then + { $as_echo "$as_me:${as_lineno-$LINENO}: $ac_file is unchanged" >&5 +$as_echo "$as_me: $ac_file is unchanged" >&6;} + else + rm -f "$ac_file" + mv "$ac_tmp/config.h" "$ac_file" \ + || as_fn_error $? "could not create $ac_file" "$LINENO" 5 + fi + else + $as_echo "/* $configure_input */" \ + && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" \ + || as_fn_error $? "could not create -" "$LINENO" 5 + fi + ;; esac diff --git a/configure.ac b/configure.ac index da399d097d081c5d5931a43bac2869d85c2495fa..b06394883dbb205e35d64f08f6fecdb478cf56f1 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([sybilSBML], [3.0.6], [mayo.roettger@hhu.de]) +AC_INIT([sybilSBML], [3.0.7], [mayo.roettger@hhu.de]) dnl # -------------------------------------------------------------------- dnl # global (environment) variables @@ -32,7 +32,7 @@ dnl # -------------------------------------------------------------------- dnl # template config.h.in dnl # -------------------------------------------------------------------- -dnl # AC_CONFIG_HEADERS([src/config.h]) +AC_CONFIG_HEADERS([src/config.h]) dnl # -------------------------------------------------------------------- @@ -239,23 +239,23 @@ 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.16 and including the FBC package.]), +AC_CHECK_HEADERS([sbml/packages/fbc/common/FbcExtensionTypes.h], , + AC_MSG_WARN([Could not find specific FBC header of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package.]), [#include <sbml/SBMLTypes.h>]) -AC_CHECK_HEADER([sbml/packages/groups/common/GroupsExtensionTypes.h], , - AC_MSG_ERROR([Could not find specific groups package header of libSBML: - make sure your libSBML version is >= 5.16 and including the groups package.]), +AC_CHECK_HEADERS([sbml/packages/groups/common/GroupsExtensionTypes.h], AC_DEFINE([HAVE_GROUPS_PLUGIN], [1], [define if Groups plugin is available]), + AC_MSG_WARN([Could not find specific groups package header of libSBML: + make sure your libSBML version is >= 5.18 and including the groups package.]), [#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.16.])) -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.16 and including the FBC package.])) +AC_CHECK_FUNCS([SBase_getPlugin SBMLExtensionRegistry_getRegisteredPackages GeneProductAssociation_setAssociation FbcReactionPlugin_getLowerFluxBound], AC_DEFINE([HAVE_FBC_PLUGIN], [1], [define if FBC plugin is available]), + AC_MSG_WARN([Could not find specific FBC function of libSBML: + make sure your libSBML version is >= 5.18 and including the FBC package.])) #AC_SEARCH_LIBS([SBase_getPlugin], [sbml], , # AC_MSG_ERROR([Could not find specific FBC function of libSBML: diff --git a/inst/NEWS.Rd b/inst/NEWS.Rd index 4aa76fe8beae83a3263bba824ee19a0d37177f96..06c5ee4841d8c865a8fe13ec695836bcf0cc68e9 100644 --- a/inst/NEWS.Rd +++ b/inst/NEWS.Rd @@ -6,6 +6,16 @@ \newcommand{\CRANpkg}{\href{https://cran.r-project.org/package=#1}{\pkg{#1}}} % ---------------------------------------------------------------------------- % +\section{Changes in version 3.0.4 - 3.0.7 2019-08-02}{ + \itemize{ + \item Maintainer change. + \item Changes to be able to build package without libSBML FBC and Groups + plugins. In that case, FBC-constraints and groups in the SBML model will + be ignored. Added functions \code{isAvailableFBCPlugin} and + \code{isAvailableGroupsPlugin}. + } +} +% ---------------------------------------------------------------------------- % \section{Changes in version 3.0.3 2018-01-02}{ \itemize{ \item Added support for the groups plugin of SBML. Now the \code{subSys} diff --git a/man/getSBMLReactionsList.Rd b/man/getSBMLReactionsList.Rd index 268e9bf4771578f1512437829d117121d58abfdb..9461121e01b253599ee5904a99e250699b8c14aa 100644 --- a/man/getSBMLReactionsList.Rd +++ b/man/getSBMLReactionsList.Rd @@ -6,7 +6,15 @@ } \description{ - Retrieve list of reactions included in a SBML model + Retrieve list of reactions included in a SBML model. + + If sybilSBML was built with a libSBML version, that was not including the FBC plugin, + FBC constraints are ignored. Please make sure that you build sybilSBML with the + libSBML version containing the FBC plugin (check out installation details). + + If sybilSBML was built with a libSBML version, that was not including the Groups plugin, + Groups are ignored. Please make sure that you build sybilSBML with the + libSBML version containing the Groups plugin (check out installation details). } \usage{ getSBMLReactionsList(sbmlm) diff --git a/man/getSBMLSpeciesList.Rd b/man/getSBMLSpeciesList.Rd index d9781a129e49ce78fdf8795a9c67b8dbbc00fe2b..e12b9835f51101bed9d7ee1681ca5f9741182260 100644 --- a/man/getSBMLSpeciesList.Rd +++ b/man/getSBMLSpeciesList.Rd @@ -6,7 +6,15 @@ } \description{ - Retrieve list of species included in a SBML model + Retrieve list of species included in a SBML model. + + If sybilSBML was built with a libSBML version, that was not including the FBC plugin, + FBC constraints are ignored. Please make sure that you build sybilSBML with the + libSBML version containing the FBC plugin (check out installation details). + + If sybilSBML was built with a libSBML version, that was not including the Groups plugin, + Groups are ignored. Please make sure that you build sybilSBML with the + libSBML version containing the Groups plugin (check out installation details). } \usage{ diff --git a/man/isAvailableFbcPlugin.Rd b/man/isAvailableFbcPlugin.Rd new file mode 100644 index 0000000000000000000000000000000000000000..c9c843a5fc454b1cbe6df815c5e2a886f20a7b10 --- /dev/null +++ b/man/isAvailableFbcPlugin.Rd @@ -0,0 +1,27 @@ +\name{isAvailableFbcPlugin} +\alias{isAvailableFbcPlugin} + +\title{ + Check for libSBML FBC plugin +} + +\description{ + Check, if sybilSBML was built with libSBML containing the FBC plugin. +} + +\usage{ + isAvailableFbcPlugin() +} + +\value{ + A single boolean value for the availability of the FBC plugin. +} + +\author{ + Mayo Roettger <mayo.roettger@hhu.de> + + Maintainer: Mayo Roettger <mayo.roettger@hhu.de> +} + + +\keyword{ IO } diff --git a/man/isAvailableGroupsPlugin.Rd b/man/isAvailableGroupsPlugin.Rd new file mode 100644 index 0000000000000000000000000000000000000000..22ec90f296773ff02f863186350e6bb4deaaa0f4 --- /dev/null +++ b/man/isAvailableGroupsPlugin.Rd @@ -0,0 +1,27 @@ +\name{isAvailableGroupsPlugin} +\alias{isAvailableGroupsPlugin} + +\title{ + Check for libSBML Groups plugin +} + +\description{ + Check, if sybilSBML was built with libSBML containing the Groups plugin. +} + +\usage{ + isAvailableFbcPlugin() +} + +\value{ + A single boolean value for the availability of the Groups plugin. +} + +\author{ + Mayo Roettger <mayo.roettger@hhu.de> + + Maintainer: Mayo Roettger <mayo.roettger@hhu.de> +} + + +\keyword{ IO } diff --git a/man/writeSBML.Rd b/man/writeSBML.Rd index caef946bcda5cfaeedd99b0bcdcd00f7b18685a2..268d20fcc5ad578c881ee429c5810e4e760a5d73 100644 --- a/man/writeSBML.Rd +++ b/man/writeSBML.Rd @@ -61,11 +61,15 @@ \details{ The library \code{libSBML} is used to export a \code{\link[sybil]{modelorg}} to a SBML file. - + + If sybilSBML was built with a libSBML version, that was not including the FBC plugin + and the Groups plugin, the function is not writing an output file and returns FALSE. + Please make sure that you build sybilSBML with the libSBML version containing the + FBC and Group plugins (check out installation details). } \value{ - A single boolean value for a successful export . + A single boolean value for a successful export. } \references{ diff --git a/src/Makevars b/src/Makevars new file mode 100644 index 0000000000000000000000000000000000000000..5838658e85fd269833f18ecd4d5efd55afdbab67 --- /dev/null +++ b/src/Makevars @@ -0,0 +1,3 @@ +PKG_CFLAGS= +PKG_CPPFLAGS=-I/usr/include -I/usr/local/include -I/usr/include/sbml -I/usr/local/include/sbml +PKG_LIBS= -L/usr/local/lib -L/usr/lib -L/usr/lib64 -lsbml diff --git a/src/config.h b/src/config.h new file mode 100644 index 0000000000000000000000000000000000000000..60423413a273333855cd80ab44d6eeff29f80032 --- /dev/null +++ b/src/config.h @@ -0,0 +1,82 @@ +/* src/config.h. Generated from config.h.in by configure. */ +/* src/config.h.in. Generated from configure.ac by autoheader. */ + +/* Define to 1 if you have the `FbcReactionPlugin_getLowerFluxBound' function. + */ +#define HAVE_FBCREACTIONPLUGIN_GETLOWERFLUXBOUND 1 + +/* define if FBC plugin is available */ +#define HAVE_FBC_PLUGIN 1 + +/* Define to 1 if you have the `GeneProductAssociation_setAssociation' + function. */ +#define HAVE_GENEPRODUCTASSOCIATION_SETASSOCIATION 1 + +/* define if Groups plugin is available */ +#define HAVE_GROUPS_PLUGIN 1 + +/* Define to 1 if you have the <inttypes.h> header file. */ +#define HAVE_INTTYPES_H 1 + +/* Define to 1 if you have the `sbml' library (-lsbml). */ +#define HAVE_LIBSBML 1 + +/* Define to 1 if you have the <memory.h> header file. */ +#define HAVE_MEMORY_H 1 + +/* Define to 1 if you have the `SBase_getPlugin' function. */ +#define HAVE_SBASE_GETPLUGIN 1 + +/* Define to 1 if you have the `SBMLExtensionRegistry_getRegisteredPackages' + function. */ +#define HAVE_SBMLEXTENSIONREGISTRY_GETREGISTEREDPACKAGES 1 + +/* Define to 1 if you have the <sbml/packages/fbc/common/FbcExtensionTypes.h> + header file. */ +#define HAVE_SBML_PACKAGES_FBC_COMMON_FBCEXTENSIONTYPES_H 1 + +/* Define to 1 if you have the + <sbml/packages/groups/common/GroupsExtensionTypes.h> header file. */ +#define HAVE_SBML_PACKAGES_GROUPS_COMMON_GROUPSEXTENSIONTYPES_H 1 + +/* Define to 1 if you have the <stdint.h> header file. */ +#define HAVE_STDINT_H 1 + +/* Define to 1 if you have the <stdlib.h> header file. */ +#define HAVE_STDLIB_H 1 + +/* Define to 1 if you have the <strings.h> header file. */ +#define HAVE_STRINGS_H 1 + +/* Define to 1 if you have the <string.h> header file. */ +#define HAVE_STRING_H 1 + +/* Define to 1 if you have the <sys/stat.h> header file. */ +#define HAVE_SYS_STAT_H 1 + +/* Define to 1 if you have the <sys/types.h> header file. */ +#define HAVE_SYS_TYPES_H 1 + +/* Define to 1 if you have the <unistd.h> header file. */ +#define HAVE_UNISTD_H 1 + +/* Define to the address where bug reports for this package should be sent. */ +#define PACKAGE_BUGREPORT "mayo.roettger@hhu.de" + +/* Define to the full name of this package. */ +#define PACKAGE_NAME "sybilSBML" + +/* Define to the full name and version of this package. */ +#define PACKAGE_STRING "sybilSBML 3.0.6" + +/* Define to the one symbol short name of this package. */ +#define PACKAGE_TARNAME "sybilsbml" + +/* Define to the home page for this package. */ +#define PACKAGE_URL "" + +/* Define to the version of this package. */ +#define PACKAGE_VERSION "3.0.6" + +/* Define to 1 if you have the ANSI C header files. */ +#define STDC_HEADERS 1 diff --git a/src/config.h.in b/src/config.h.in new file mode 100644 index 0000000000000000000000000000000000000000..099e987d269d66ccec846e72c0520a2632027b41 --- /dev/null +++ b/src/config.h.in @@ -0,0 +1,81 @@ +/* src/config.h.in. Generated from configure.ac by autoheader. */ + +/* Define to 1 if you have the `FbcReactionPlugin_getLowerFluxBound' function. + */ +#undef HAVE_FBCREACTIONPLUGIN_GETLOWERFLUXBOUND + +/* define if FBC plugin is available */ +#undef HAVE_FBC_PLUGIN + +/* Define to 1 if you have the `GeneProductAssociation_setAssociation' + function. */ +#undef HAVE_GENEPRODUCTASSOCIATION_SETASSOCIATION + +/* define if Groups plugin is available */ +#undef HAVE_GROUPS_PLUGIN + +/* Define to 1 if you have the <inttypes.h> header file. */ +#undef HAVE_INTTYPES_H + +/* Define to 1 if you have the `sbml' library (-lsbml). */ +#undef HAVE_LIBSBML + +/* Define to 1 if you have the <memory.h> header file. */ +#undef HAVE_MEMORY_H + +/* Define to 1 if you have the `SBase_getPlugin' function. */ +#undef HAVE_SBASE_GETPLUGIN + +/* Define to 1 if you have the `SBMLExtensionRegistry_getRegisteredPackages' + function. */ +#undef HAVE_SBMLEXTENSIONREGISTRY_GETREGISTEREDPACKAGES + +/* Define to 1 if you have the <sbml/packages/fbc/common/FbcExtensionTypes.h> + header file. */ +#undef HAVE_SBML_PACKAGES_FBC_COMMON_FBCEXTENSIONTYPES_H + +/* Define to 1 if you have the + <sbml/packages/groups/common/GroupsExtensionTypes.h> header file. */ +#undef HAVE_SBML_PACKAGES_GROUPS_COMMON_GROUPSEXTENSIONTYPES_H + +/* Define to 1 if you have the <stdint.h> header file. */ +#undef HAVE_STDINT_H + +/* Define to 1 if you have the <stdlib.h> header file. */ +#undef HAVE_STDLIB_H + +/* Define to 1 if you have the <strings.h> header file. */ +#undef HAVE_STRINGS_H + +/* Define to 1 if you have the <string.h> header file. */ +#undef HAVE_STRING_H + +/* Define to 1 if you have the <sys/stat.h> header file. */ +#undef HAVE_SYS_STAT_H + +/* Define to 1 if you have the <sys/types.h> header file. */ +#undef HAVE_SYS_TYPES_H + +/* Define to 1 if you have the <unistd.h> header file. */ +#undef HAVE_UNISTD_H + +/* Define to the address where bug reports for this package should be sent. */ +#undef PACKAGE_BUGREPORT + +/* Define to the full name of this package. */ +#undef PACKAGE_NAME + +/* Define to the full name and version of this package. */ +#undef PACKAGE_STRING + +/* Define to the one symbol short name of this package. */ +#undef PACKAGE_TARNAME + +/* Define to the home page for this package. */ +#undef PACKAGE_URL + +/* Define to the version of this package. */ +#undef PACKAGE_VERSION + +/* Define to 1 if you have the ANSI C header files. */ +#undef STDC_HEADERS diff --git a/src/init.c b/src/init.c index ef92c062b6264fd79e9641d5d914498c0d0d21eb..89e831f3a03b1de23304dbe68768d27dfad63afe 100644 --- a/src/init.c +++ b/src/init.c @@ -1,69 +1,71 @@ -/* init.c - Link to libSBML for sybil. - - Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, - Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. - All right reserved. - Email: geliudie@uni-duesseldorf.de - - This file is part of sybilSBML. - - SybilSBML is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - SybilSBML is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. -*/ - -#include <R.h> -#include <Rinternals.h> - -#include "sybilSBML.h" - -#include <R_ext/Rdynload.h> - -static const R_CallMethodDef callMethods[] = { - {"isSBMLdocptr", (DL_FUNC) &isSBMLdocptr, 1}, - {"isSBMLmodptr", (DL_FUNC) &isSBMLmodptr, 1}, - {"isNULLptr", (DL_FUNC) &isNULLptr, 1}, - {"getLibSBMLversion", (DL_FUNC) &getLibSBMLversion, 0}, - {"initSBML", (DL_FUNC) &initSBML, 0}, - {"delDocument", (DL_FUNC) &delDocument, 1}, - {"delModel", (DL_FUNC) &delModel, 1}, - {"readSBMLfile", (DL_FUNC) &readSBMLfile, 2}, - {"getSBMLlevel", (DL_FUNC) &getSBMLlevel, 1}, - {"getSBMLversion", (DL_FUNC) &getSBMLversion, 1}, - {"validateDocument", (DL_FUNC) &validateDocument, 1}, - {"getSBMLerrors", (DL_FUNC) &getSBMLerrors, 1}, - {"getSBMLGroupsList", (DL_FUNC) &getSBMLGroupsList, 1}, - {"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}, - {"getSBMLunitDefinitionsList", (DL_FUNC) &getSBMLunitDefinitionsList, 1}, - {"getSBMLCompartList", (DL_FUNC) &getSBMLCompartList, 1}, - {"getSBMLSpeciesList", (DL_FUNC) &getSBMLSpeciesList, 1}, - {"getSBMLReactionsList", (DL_FUNC) &getSBMLReactionsList, 1}, - {"exportSBML", (DL_FUNC) &exportSBML, 34}, - {"getSBMLFbcversion", (DL_FUNC) &getSBMLFbcversion, 1}, - {NULL, NULL, 0} -}; - - -/* -------------------------------------------------------------------------- */ - -void R_init_sybilSBML(DllInfo *info) { - R_registerRoutines(info, NULL, callMethods, NULL, NULL); - R_useDynamicSymbols(info, FALSE); -} +/* init.c + Link to libSBML for sybil. + + Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, + Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. + All right reserved. + Email: geliudie@uni-duesseldorf.de + + This file is part of sybilSBML. + + SybilSBML is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + SybilSBML is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. +*/ + +#include <R.h> +#include <Rinternals.h> + +#include "sybilSBML.h" + +#include <R_ext/Rdynload.h> + +static const R_CallMethodDef callMethods[] = { + {"isSBMLdocptr", (DL_FUNC) &isSBMLdocptr, 1}, + {"isSBMLmodptr", (DL_FUNC) &isSBMLmodptr, 1}, + {"isNULLptr", (DL_FUNC) &isNULLptr, 1}, + {"getLibSBMLversion", (DL_FUNC) &getLibSBMLversion, 0}, + {"initSBML", (DL_FUNC) &initSBML, 0}, + {"delDocument", (DL_FUNC) &delDocument, 1}, + {"delModel", (DL_FUNC) &delModel, 1}, + {"readSBMLfile", (DL_FUNC) &readSBMLfile, 2}, + {"getSBMLlevel", (DL_FUNC) &getSBMLlevel, 1}, + {"getSBMLversion", (DL_FUNC) &getSBMLversion, 1}, + {"validateDocument", (DL_FUNC) &validateDocument, 1}, + {"getSBMLerrors", (DL_FUNC) &getSBMLerrors, 1}, + {"getSBMLGroupsList", (DL_FUNC) &getSBMLGroupsList, 1}, + {"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}, + {"getSBMLunitDefinitionsList", (DL_FUNC) &getSBMLunitDefinitionsList, 1}, + {"getSBMLCompartList", (DL_FUNC) &getSBMLCompartList, 1}, + {"getSBMLSpeciesList", (DL_FUNC) &getSBMLSpeciesList, 1}, + {"getSBMLReactionsList", (DL_FUNC) &getSBMLReactionsList, 1}, + {"exportSBML", (DL_FUNC) &exportSBML, 34}, + {"getSBMLFbcversion", (DL_FUNC) &getSBMLFbcversion, 1}, + {"isAvailableFbcPlugin", (DL_FUNC) &isAvailableFbcPlugin, 0}, + {"isAvailableGroupsPlugin", (DL_FUNC) &isAvailableGroupsPlugin, 0}, + {NULL, NULL, 0} +}; + + +/* -------------------------------------------------------------------------- */ + +void R_init_sybilSBML(DllInfo *info) { + R_registerRoutines(info, NULL, callMethods, NULL, NULL); + R_useDynamicSymbols(info, FALSE); +} diff --git a/src/sbml.h b/src/sbml.h index 4d3b9c9a889a33a3d7eab69a600aabeb94fb263f..d745e564a149bcfe2a13a33de618a970953e9c68 100644 --- a/src/sbml.h +++ b/src/sbml.h @@ -39,6 +39,9 @@ #include <R.h> #include <Rinternals.h> +#ifdef HAVE_CONFIG_H +#include "config.h" +#endif /* HAVE_CONFIG_H */ /* -------------------------------------------------------------------------- */ /* NULL */ diff --git a/src/sybilSBML.c b/src/sybilSBML.c index 61b3d174e65d8735baa7b8eb0ca24be09b87b3a2..32e1b948a749a5f1bd73515d474a2c0d25c61b0a 100644 --- a/src/sybilSBML.c +++ b/src/sybilSBML.c @@ -1,2365 +1,2424 @@ -/* sybilSBML.c - Link to libSBML for sybil. - - Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, -Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. -All right reserved. -Email: geliudie@uni-duesseldorf.de - -This file is part of sybilSBML. - -SybilSBML is free software: you can redistribute it and/or modify -it under the terms of the GNU General Public License as published by -the Free Software Foundation, either version 3 of the License, or -(at your option) any later version. - -SybilSBML is distributed in the hope that it will be useful, -but WITHOUT ANY WARRANTY; without even the implied warranty of -MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -GNU General Public License for more details. - -You should have received a copy of the GNU General Public License -along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. -*/ - - -#include "sybilSBML.h" - -//new includes @Ardalan Habil -#include <stdlib.h> -#include <string.h> -#include <sbml/xml/XMLTriple.h> -#include <sbml/annotation/CVTerm.h> -#include <sbml/annotation/RDFAnnotationParser.h> -#include <sbml/annotation/ModelHistory.h> -#include <sbml/math/ASTNode.h> -#include <math.h> - -/* FBCv1includes */ - -#include <sbml/extension/SBMLExtensionRegister.h> -#include <sbml/extension/SBMLDocumentPlugin.h> - -#include <sbml/packages/fbc/common/fbcfwd.h> - -/* FBC PLUGINS*/ -#include <sbml/packages/fbc/extension/FbcSBMLDocumentPlugin.h> -#include <sbml/packages/fbc/extension/FbcModelPlugin.h> -#include <sbml/packages/fbc/extension/FbcReactionPlugin.h> -#include <sbml/packages/fbc/extension/FbcSpeciesPlugin.h> - -#include <sbml/packages/fbc/sbml/FluxBound.h> -#include <sbml/packages/fbc/sbml/Objective.h> -#include <sbml/packages/fbc/sbml/FluxObjective.h> -#include <sbml/packages/fbc/sbml/GeneProduct.h> -#include <sbml/packages/fbc/sbml/GeneProductRef.h> -#include <sbml/packages/fbc/sbml/GeneProductAssociation.h> -#include <sbml/packages/fbc/sbml/FbcAssociation.h> -#include <sbml/packages/fbc/sbml/FbcAnd.h> -#include <sbml/packages/fbc/sbml/FbcOr.h> - -/*groups plugin*/ -#include <sbml/packages/groups/common/GroupsExtensionTypes.h> -#include <sbml/packages/groups/extension/GroupsSBMLDocumentPlugin.h> -#include <sbml/packages/groups/extension/GroupsExtension.h> -#include <sbml/packages/groups/extension/GroupsModelPlugin.h> - -#include <sbml/packages/groups/sbml/Group.h> -#include <sbml/packages/groups/sbml/ListOfGroups.h> -#include <sbml/packages/groups/sbml/ListOfMembers.h> -#include <sbml/packages/groups/sbml/Member.h> - - -static SEXP tagSBMLmodel; -static SEXP tagSBMLdocument; - - -/* -------------------------------------------------------------------------- */ -/* Finalizer */ -/* -------------------------------------------------------------------------- */ - -/* -------------------------------------------------------------------------- */ -/* finalizer for sbml document objects */ -static void sbmlDocumentFinalizer (SEXP sbmldoc) { - if (!R_ExternalPtrAddr(sbmldoc)) { - return; - } - else { - delDocument(sbmldoc); - } -} - - -/* -------------------------------------------------------------------------- */ -/* finalizer for sbml model objects */ -/* -static void sbmlModelFinalizer (SEXP sbmlmodel) { -if (!R_ExternalPtrAddr(sbmlmodel)) { -return; -} -else { -delModel(sbmlmodel); -} -} -*/ - - -/* -------------------------------------------------------------------------- */ -/* help functions */ -/* -------------------------------------------------------------------------- */ - -/* check for pointer to sbml document */ -SEXP isSBMLdocptr(SEXP ptr) { - - SEXP out = R_NilValue; - - if ( (TYPEOF(ptr) == EXTPTRSXP) && - (R_ExternalPtrTag(ptr) == tagSBMLdocument) ) { - out = Rf_ScalarLogical(1); - } - else { - out = Rf_ScalarLogical(0); - } - - return out; -} - -/* check for pointer to sbml model */ -SEXP isSBMLmodptr(SEXP ptr) { - - SEXP out = R_NilValue; - - if ( (TYPEOF(ptr) == EXTPTRSXP) && - (R_ExternalPtrTag(ptr) == tagSBMLmodel) ) { - out = Rf_ScalarLogical(1); - } - else { - out = Rf_ScalarLogical(0); - } - - return out; -} - -/* check for NULL pointer */ -SEXP isNULLptr(SEXP ptr) { - - SEXP out = R_NilValue; - - if ( (TYPEOF(ptr) == EXTPTRSXP) && - (R_ExternalPtrAddr(ptr) == NULL) ) { - out = Rf_ScalarLogical(1); - } - else { - out = Rf_ScalarLogical(0); - } - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* Helper functions */ -/* -------------------------------------------------------------------------- */ - - -// append two string -char * append_strings(const char * old, const char * new, const char* delim) -{ - // find the size of the string to allocate - size_t len = strlen(old) + strlen(new) + strlen(delim) + 1; - - // allocate a pointer to the new string - char *out = malloc(len); - - // concat both strings and return - sprintf(out, "%s%s%s", old, delim , new); - - return out; -} - - - -// Parse Anntatation to modelorg -const char* parseAnnotationTomorg(XMLNode_t* xml) -{ - const XMLNode_t* rdf =NULL; - const XMLNode_t* desc = NULL; - rdf = XMLNode_getChildForName(xml,"RDF"); - if(rdf !=NULL) desc= XMLNode_getChildForName(rdf,"Description"); - const char* annoString = ""; - int firstelement=1; - if (desc!=NULL) - { - - int num=0; - for(num=0;num<XMLNode_getNumChildren(desc);num++) - { - const char* pref= XMLNode_getPrefix(XMLNode_getChild(desc,num)); - - if( strcmp(pref,"bqbiol")==0 || strcmp(pref,"bqmodel")==0 ) - { - CVTerm_t* cv= CVTerm_createFromNode(XMLNode_getChild(desc,num)); - if( CVTerm_getNumResources(cv)>0 ) - { - int numR=0; - if(strcmp(pref,"bqbiol")==0) - { - const char* bioQual = append_strings("bqbiol",BiolQualifierType_toString( CVTerm_getBiologicalQualifierType(cv)),"_"); - if(firstelement==0) annoString = append_strings(annoString,bioQual,";"); - else - { - annoString = append_strings(annoString,bioQual,""); - firstelement=0; - } - - } - if(strcmp(pref,"bqmodel")==0) - { - const char* modQual = append_strings("bqmodel",ModelQualifierType_toString( CVTerm_getModelQualifierType(cv)),"_"); - if(firstelement==0)annoString = append_strings(annoString,modQual,";"); - - else - { - annoString = append_strings(annoString,modQual,""); - firstelement=0; - } - } - - for(numR=0;numR<CVTerm_getNumResources(cv);numR++) - { - // sprintf(annoString+strlen(annoString),"__%s", CVTerm_getResourceURI(cv,numR)); - annoString = append_strings(annoString,CVTerm_getResourceURI(cv,numR),";"); - } - - } - } - - - } - return annoString; - } - else - { - return ""; - } - - - return ""; -} - - - -/* -------------------------------------------------------------------------- */ -/* API-Functions */ -/* -------------------------------------------------------------------------- */ - -/* -------------------------------------------------------------------------- */ -/* initialize sybilSBML */ -SEXP initSBML(void) { - tagSBMLmodel = Rf_install("TYPE_SBML_MODEL"); - tagSBMLdocument = Rf_install("TYPE_SBML_DOCUMENT"); - return R_NilValue; -} - - -/* -------------------------------------------------------------------------- */ -/* get libsbml version number (dotted version) */ -SEXP getLibSBMLversion() { - - SEXP out = R_NilValue; - - const char *vstr = getLibSBMLDottedVersion(); - - out = Rf_mkString(vstr); - - return out; - -} - - -/* -------------------------------------------------------------------------- */ -/* remove sbml document pointer */ -SEXP delDocument(SEXP sbmldoc) { - - SEXP out = R_NilValue; - SBMLDocument_t *del = NULL; - - checkDocument(sbmldoc); - - del = R_ExternalPtrAddr(sbmldoc); - - SBMLDocument_free(del); - R_ClearExternalPtr(sbmldoc); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* remove model pointer */ -SEXP delModel(SEXP sbmlmodel) { - - SEXP out = R_NilValue; - /* Model_t *del = NULL; */ - - checkModel(sbmlmodel); - - /* del = R_ExternalPtrAddr(sbmlmodel); */ - - /* Model_free(del); */ - R_ClearExternalPtr(sbmlmodel); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* read SBML file */ -SEXP readSBMLfile(SEXP fname, SEXP ptrtype) { - - SEXP sfext = R_NilValue; - SEXP ptr, class, file; - const char *rfname = CHAR(STRING_ELT(fname, 0)); - - SBMLDocument_t *sbmldoc; - - /* create sbml document pointer */ - PROTECT(ptr = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(ptr, 0, STRING_ELT(ptrtype, 0)); - - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("sbml_doc_ptr")); - - PROTECT(file = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(file, 0, Rf_mkChar("file_name")); - - /* read the model xml file */ - sbmldoc = readSBML(rfname); - - sfext = R_MakeExternalPtr(sbmldoc, tagSBMLdocument, R_NilValue); - PROTECT(sfext); - R_RegisterCFinalizerEx(sfext, sbmlDocumentFinalizer, TRUE); - Rf_setAttrib(ptr, class, sfext); - Rf_setAttrib(ptr, file, fname); - Rf_classgets(ptr, class); - - UNPROTECT(4); - - return ptr; -} - - -/* -------------------------------------------------------------------------- */ -/* get sbml document level */ -SEXP getSBMLlevel(SEXP sbmldoc) { - - SEXP out = R_NilValue; - unsigned int level; - - checkDocument(sbmldoc); - - level = SBMLDocument_getLevel(R_ExternalPtrAddr(sbmldoc)); - - out = Rf_ScalarInteger(level); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get sbml document version */ -SEXP getSBMLversion(SEXP sbmldoc) { - - SEXP out = R_NilValue; - unsigned int version; - - checkDocument(sbmldoc); - - version = SBMLDocument_getVersion(R_ExternalPtrAddr(sbmldoc)); - - out = Rf_ScalarInteger(version); - - return out; -} - - -/* -------------------------------------------------------------------------- */ - -/* get sbml document FBC version */ -SEXP getSBMLFbcversion(SEXP sbmldoc) { - - SEXP out = R_NilValue; - unsigned int version; - - checkDocument(sbmldoc); - //hierher - SBasePlugin_t * modelPlug= NULL; - modelPlug = SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmldoc)), "fbc"); - if( modelPlug != NULL) - { - if(strcmp("fbc",SBasePlugin_getPackageName(modelPlug) ) ==0) - version = SBasePlugin_getPackageVersion(modelPlug); - else version=0; - } else version=0; - - out = Rf_ScalarInteger(version); - - return out; -} - - -/* -------------------------------------------------------------------------- */ - - -/* validate SBML document */ -SEXP validateDocument(SEXP sbmldoc) { - - /* - this is adopted from Michael Lawrence: rsbml - Michael Lawrence (). rsbml: R support for SBML, using libsbml. - R package version 2.18.0. http://www.sbml.org - http://www.bioconductor.org/packages/release/bioc/html/rsbml.html - */ - - SEXP out = R_NilValue; - - unsigned int validation; - - checkDocument(sbmldoc); - - /* number or errors logged when reading SBML file */ - validation = SBMLDocument_getNumErrors(R_ExternalPtrAddr(sbmldoc)); - /* number or errors from structural and mathematical tests */ - validation += SBMLDocument_checkConsistency(R_ExternalPtrAddr(sbmldoc)); - - if (validation > 0) { - out = Rf_ScalarLogical(0); - } - else { - out = Rf_ScalarLogical(1); - } - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get SBML errors */ -SEXP getSBMLerrors(SEXP sbmldoc) { - - /* - this is adopted from Michael Lawrence: rsbml - Michael Lawrence (). rsbml: R support for SBML, using libsbml. - R package version 2.18.0. http://www.sbml.org - http://www.bioconductor.org/packages/release/bioc/html/rsbml.html - */ - - SEXP out = R_NilValue; - SEXP listv = R_NilValue; - SEXP info = R_NilValue; - SEXP warn = R_NilValue; - SEXP error = R_NilValue; - SEXP fatal = R_NilValue; - SEXP class = R_NilValue; - SEXP el = R_NilValue; - - XMLError_t *sbml_err; - - unsigned int nprob, i, ind; - int ninfo = 0, nwarn = 0, nerror = 0, nfatal = 0, nunknown = 0; - - checkDocument(sbmldoc); - - nprob = SBMLDocument_getNumErrors(R_ExternalPtrAddr(sbmldoc)); - - /* - Rprintf("Model Errors: %i\n", nprob); - */ - - if (nprob > 0) { - - /* check how many infos, warnings, errors and fatals we have */ - for (i = 0; i < nprob; i++) { - sbml_err = (XMLError_t *) SBMLDocument_getError(R_ExternalPtrAddr(sbmldoc), i); - if (XMLError_isInfo(sbml_err)) { - ninfo++; - } - else if (XMLError_isWarning(sbml_err)) { - nwarn++; - } - else if (XMLError_isError(sbml_err)) { - nerror++; - } - else if (XMLError_isFatal(sbml_err)) { - nfatal++; - } - else { - nunknown++; - } - } - - /* - Rprintf("number of infos: %i, warnings: %i, errors: %i, falals: %i, unknowns: %i\n", - ninfo, nwarn, nerror, nfatal, nunknown); - */ - - /* - out will be a list of four elements: - infos - warnings - errors - fatals - each of them is a list of three elements: - id - line - column - msg - */ - - PROTECT(out = Rf_allocVector(VECSXP, 4)); - - /* allocate space for each error list */ - PROTECT(info = Rf_allocVector(VECSXP, ninfo)); - PROTECT(warn = Rf_allocVector(VECSXP, nwarn)); - PROTECT(error = Rf_allocVector(VECSXP, nerror)); - PROTECT(fatal = Rf_allocVector(VECSXP, nfatal)); - - SET_VECTOR_ELT(out, 0, info); - SET_VECTOR_ELT(out, 1, warn); - SET_VECTOR_ELT(out, 2, error); - SET_VECTOR_ELT(out, 3, fatal); - - PROTECT(listv = Rf_allocVector(STRSXP, 4)); - SET_STRING_ELT(listv, 0, Rf_mkChar("infos")); - SET_STRING_ELT(listv, 1, Rf_mkChar("warnings")); - SET_STRING_ELT(listv, 2, Rf_mkChar("errors")); - SET_STRING_ELT(listv, 3, Rf_mkChar("fatals")); - Rf_setAttrib(out, R_NamesSymbol, listv); - - /* get the error messages */ - ninfo = 0, nwarn = 0, nerror = 0, nfatal = 0, nunknown = 0; - for (i = 0; i < nprob; i++) { - sbml_err = (XMLError_t *) SBMLDocument_getError(R_ExternalPtrAddr(sbmldoc), i); - el = R_NilValue; - ind = 0; - if (XMLError_isInfo(sbml_err)) { - ind = ninfo++; - el = info; - } - else if (XMLError_isWarning(sbml_err)) { - ind = nwarn++; - el = warn; - } - else if (XMLError_isError(sbml_err)) { - ind = nerror++; - el = error; - } - else if (XMLError_isFatal(sbml_err)) { - ind = nfatal++; - el = fatal; - } - else { - nunknown++; - } - SET_VECTOR_ELT(el, ind, generateProblemMsg(sbml_err)); - } - - /* make the list to be an instance of 'sbml_error' */ - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("sbml_error")); - Rf_classgets(out, class); - - UNPROTECT(7); - - } /* end if nprob > 0 */ - else { - out = Rf_ScalarLogical(1); - } - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get sbml model from sbml document */ -SEXP getSBMLmodel(SEXP sbmldoc, SEXP ptrtype) { - - SEXP smext = R_NilValue; - SEXP ptr, class; - - Model_t *sbmlmodel; - - checkDocument(sbmldoc); - - /* create model pointer */ - PROTECT(ptr = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(ptr, 0, STRING_ELT(ptrtype, 0)); - - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("sbml_model_ptr")); - - /* get sbml model */ - sbmlmodel = SBMLDocument_getModel(R_ExternalPtrAddr(sbmldoc)); - - smext = R_MakeExternalPtr(sbmlmodel, tagSBMLmodel, R_NilValue); - PROTECT(smext); - /* R_RegisterCFinalizerEx(smext, sbmlModelFinalizer, TRUE); */ - Rf_setAttrib(ptr, class, smext); - Rf_classgets(ptr, class); - - UNPROTECT(3); - - return ptr; -} - - -/* -------------------------------------------------------------------------- */ -/* get model id */ -SEXP getSBMLmodId(SEXP sbmlmod) { - - SEXP out = R_NilValue; - const char *mid; - - checkModel(sbmlmod); - - if (Model_isSetId(R_ExternalPtrAddr(sbmlmod))) { - mid = Model_getId(R_ExternalPtrAddr(sbmlmod)); - } - else { - mid = "no_id"; - } - - out = Rf_mkString(mid); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get model name */ -SEXP getSBMLmodName(SEXP sbmlmod) { - - SEXP out = R_NilValue; - const char *mnm; - - checkModel(sbmlmod); - - if (Model_isSetName(R_ExternalPtrAddr(sbmlmod))) { - mnm = Model_getName(R_ExternalPtrAddr(sbmlmod)); - } - else { - mnm = ""; - } - - out = Rf_mkString(mnm); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get model notes */ -SEXP getSBMLmodNotes(SEXP sbmlmod) { - - SEXP out = R_NilValue; - const char *mnotes; - - checkModel(sbmlmod); - - if (SBase_isSetNotes((SBase_t *) R_ExternalPtrAddr(sbmlmod))) { - mnotes = SBase_getNotesString((SBase_t *) R_ExternalPtrAddr(sbmlmod)); - } - else { - mnotes = ""; - } - - out = Rf_mkString(mnotes); - - return out; -} - -/* -------------------------------------------------------------------------- */ -/* get model name */ -SEXP getSBMLmodAnnotation(SEXP sbmlmod) { - - SEXP out = R_NilValue; - const char *manno; - - checkModel(sbmlmod); - - if (SBase_isSetAnnotation((SBase_t *) R_ExternalPtrAddr(sbmlmod))) { - XMLNode_t* xml = SBase_getAnnotation((SBase_t *) R_ExternalPtrAddr(sbmlmod)); - manno = parseAnnotationTomorg(xml); - } - else { - manno = ""; - } - - out = Rf_mkString(manno); - - return out; -} - - - -/* -------------------------------------------------------------------------- */ -/* get number of compartments */ -SEXP getSBMLnumCompart(SEXP sbmlmod) { - - SEXP out = R_NilValue; - unsigned int nc; - - checkModel(sbmlmod); - - nc = Model_getNumCompartments(R_ExternalPtrAddr(sbmlmod)); - - out = Rf_ScalarInteger(nc); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get number of species (metabolites) */ -SEXP getSBMLnumSpecies(SEXP sbmlmod) { - - SEXP out = R_NilValue; - unsigned int nsp; - - checkModel(sbmlmod); - - nsp = Model_getNumSpecies(R_ExternalPtrAddr(sbmlmod)); - - out = Rf_ScalarInteger(nsp); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get number of reactions */ -SEXP getSBMLnumReactions(SEXP sbmlmod) { - - SEXP out = R_NilValue; - unsigned int nr; - - checkModel(sbmlmod); - - nr = Model_getNumReactions(R_ExternalPtrAddr(sbmlmod)); - - out = Rf_ScalarInteger(nr); - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get list of unit definitions */ -SEXP getSBMLunitDefinitionsList(SEXP sbmlmod) { - - SEXP out = R_NilValue; - SEXP class = R_NilValue; - SEXP unl = R_NilValue; - SEXP listv = R_NilValue; - SEXP listn = R_NilValue; - - SEXP unitdefid = R_NilValue; - SEXP unitdef = R_NilValue; - - SEXP unitkind = R_NilValue; - SEXP unitscale = R_NilValue; - SEXP unitexp = R_NilValue; - SEXP unitmult = R_NilValue; - - unsigned int nud, nu, i, j; - - /* ListOf_t *udl; */ - UnitDefinition_t *udlel; - Unit_t *uel; - - checkModel(sbmlmod); - - /* udl = Model_getListOfUnitDefinitions(R_ExternalPtrAddr(sbmlmod)); */ - nud = Model_getNumUnitDefinitions(R_ExternalPtrAddr(sbmlmod)); - - if (nud > 0) { - PROTECT(unitdefid = Rf_allocVector(STRSXP, nud)); - PROTECT(unitdef = Rf_allocVector(VECSXP, nud)); - for (i = 0; i < nud; i++) { - /* udlel = (UnitDefinition_t *) ListOf_get(udl, i); */ - udlel = Model_getUnitDefinition(R_ExternalPtrAddr(sbmlmod), i); - - /* id and unit */ - if (UnitDefinition_isSetId(udlel)) { - SET_STRING_ELT(unitdefid, i, Rf_mkChar(UnitDefinition_getId(udlel))); - - nu = UnitDefinition_getNumUnits(udlel); - - PROTECT(unitkind = Rf_allocVector(STRSXP, nu)); - PROTECT(unitscale = Rf_allocVector(INTSXP, nu)); - PROTECT(unitexp = Rf_allocVector(INTSXP, nu)); - PROTECT(unitmult = Rf_allocVector(REALSXP, nu)); - - for (j = 0; j < nu; j++) { - uel = UnitDefinition_getUnit(udlel, j); - - /* kind */ - if (Unit_isSetKind(uel)) { - SET_STRING_ELT(unitkind, j, Rf_mkChar(UnitKind_toString(Unit_getKind(uel)))); - } - else { - SET_STRING_ELT(unitkind, j, Rf_mkChar("no_kind")); - } - - /* scale */ - if (Unit_isSetScale(uel)) { - INTEGER(unitscale)[j] = Unit_getScale(uel); - } - else { - INTEGER(unitscale)[j] = 0; - } - - /* exponent */ - if (Unit_isSetExponent(uel)) { - INTEGER(unitexp)[j] = Unit_getExponent(uel); - } - else { - INTEGER(unitexp)[j] = 1; - } - - /* multiplier */ - if (Unit_isSetMultiplier(uel)) { - REAL(unitmult)[j] = Unit_getMultiplier(uel); - } - else { - REAL(unitmult)[j] = 1; - } - - } - - PROTECT(unl = Rf_allocVector(VECSXP, 4)); - SET_VECTOR_ELT(unl, 0, unitkind); - SET_VECTOR_ELT(unl, 1, unitscale); - SET_VECTOR_ELT(unl, 2, unitexp); - SET_VECTOR_ELT(unl, 3, unitmult); - - PROTECT(listn = Rf_allocVector(STRSXP, 4)); - SET_STRING_ELT(listn, 0, Rf_mkChar("kind")); - SET_STRING_ELT(listn, 1, Rf_mkChar("scale")); - SET_STRING_ELT(listn, 2, Rf_mkChar("exponent")); - SET_STRING_ELT(listn, 3, Rf_mkChar("multiplier")); - Rf_setAttrib(unl, R_NamesSymbol, listn); - - SET_VECTOR_ELT(unitdef, i, unl); - - UNPROTECT(6); - - } - else { - SET_STRING_ELT(unitdefid, i, Rf_mkChar("no_id")); - } - } - - PROTECT(out = Rf_allocVector(VECSXP, 2)); - SET_VECTOR_ELT(out, 0, unitdefid); - SET_VECTOR_ELT(out, 1, unitdef); - - PROTECT(listv = Rf_allocVector(STRSXP, 2)); - SET_STRING_ELT(listv, 0, Rf_mkChar("definition_id")); - SET_STRING_ELT(listv, 1, Rf_mkChar("definition")); - - Rf_setAttrib(out, R_NamesSymbol, listv); - - /* make the list to be an instance of 'unit_definition' */ - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("unit_definition")); - Rf_classgets(out, class); - - UNPROTECT(5); - } - else { - out = R_NilValue; - } - - return out; -} - - -/* -------------------------------------------------------------------------- */ -/* get list of compartments */ -SEXP getSBMLCompartList(SEXP sbmlmod) { - - SEXP out = R_NilValue; - SEXP class = R_NilValue; - SEXP listv = R_NilValue; - SEXP compid = R_NilValue; - SEXP compname = R_NilValue; - SEXP compannot = R_NilValue; - SEXP compnotes = R_NilValue; - SEXP compout = R_NilValue; - - unsigned int nc, i; - - /* ListOf_t *cl; */ - Compartment_t *clel; - - checkModel(sbmlmod); - - /* cl = Model_getListOfCompartments(R_ExternalPtrAddr(sbmlmod)); */ - nc = Model_getNumCompartments(R_ExternalPtrAddr(sbmlmod)); - - if (nc > 0) { - PROTECT(compid = Rf_allocVector(STRSXP, nc)); - PROTECT(compname = Rf_allocVector(STRSXP, nc)); - PROTECT(compannot = Rf_allocVector(STRSXP, nc)); - PROTECT(compnotes = Rf_allocVector(STRSXP, nc)); - - // Counter Variables - int annocount=0; - int notescount=0; - - PROTECT(compout = Rf_allocVector(STRSXP, nc)); - - for (i = 0; i < nc; i++) { - clel = Model_getCompartment(R_ExternalPtrAddr(sbmlmod), i); - /* id */ - if (Compartment_isSetId(clel)) { - SET_STRING_ELT(compid, i, Rf_mkChar(Compartment_getId(clel))); - } - else { - SET_STRING_ELT(compid, i, Rf_mkChar("no_id")); - } - /* name */ - if (Compartment_isSetName(clel)) { - SET_STRING_ELT(compname, i, Rf_mkChar(Compartment_getName(clel))); - } - else { - SET_STRING_ELT(compname, i, Rf_mkChar("")); - } - /* outside */ - if (Compartment_isSetOutside(clel)) { - SET_STRING_ELT(compout, i, Rf_mkChar(Compartment_getOutside(clel))); - } - else { - SET_STRING_ELT(compout, i, Rf_mkChar("")); - } - - /* NEW INFORMATIONS*/ - /* notes */ - if (SBase_isSetNotes((SBase_t *) clel)) { - SET_STRING_ELT(compnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) clel))); - notescount=notescount+1; - } - else { - SET_STRING_ELT(compnotes, i, Rf_mkChar("")); - } - - /* annotation */ - if (SBase_isSetAnnotation((SBase_t *) clel)) { - XMLNode_t* xml = SBase_getAnnotation((SBase_t *) clel); - SET_STRING_ELT(compannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); - annocount=annocount+1; - } - else { - SET_STRING_ELT(compannot, i, Rf_mkChar("")); - } - - - } - - // NULL if empty - if (annocount==0) compannot = R_NilValue; - if (notescount==0) compnotes = R_NilValue; - - PROTECT(out = Rf_allocVector(VECSXP, 5)); - SET_VECTOR_ELT(out, 0, compid); - SET_VECTOR_ELT(out, 1, compname); - SET_VECTOR_ELT(out, 2, compout); - SET_VECTOR_ELT(out, 3, compannot); - SET_VECTOR_ELT(out, 4, compnotes); - - - PROTECT(listv = Rf_allocVector(STRSXP, 5)); - SET_STRING_ELT(listv, 0, Rf_mkChar("id")); - SET_STRING_ELT(listv, 1, Rf_mkChar("name")); - SET_STRING_ELT(listv, 2, Rf_mkChar("outside")); - SET_STRING_ELT(listv, 3, Rf_mkChar("annotation")); - SET_STRING_ELT(listv, 4, Rf_mkChar("notes")); - - - - Rf_setAttrib(out, R_NamesSymbol, listv); - - /* make the list to be an instance of 'compartments_list' */ - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("compartments_list")); - Rf_classgets(out, class); - - UNPROTECT(8); - } - else { - out = R_NilValue; - } - - return out; -} - -/* -------------------------------------------------------------------------- */ -/* get list of species (metabolites) */ -SEXP getSBMLSpeciesList(SEXP sbmlmod) { - - SEXP out = R_NilValue; - SEXP class = R_NilValue; - SEXP listv = R_NilValue; - SEXP metid = R_NilValue; - SEXP metname = R_NilValue; - SEXP metcomp = R_NilValue; - SEXP metcharge = R_NilValue; - SEXP metchemic = R_NilValue; - SEXP metbndcnd = R_NilValue; - SEXP metannot = R_NilValue; - SEXP metnotes = R_NilValue; - - unsigned int nsp, i; - - /* ListOf_t *spl; */ - Species_t *splel; - - checkModel(sbmlmod); - - /* spl = Model_getListOfSpecies(R_ExternalPtrAddr(sbmlmod)); */ - nsp = Model_getNumSpecies(R_ExternalPtrAddr(sbmlmod)); - - - if (nsp > 0) { - PROTECT(metid = Rf_allocVector(STRSXP, nsp)); - PROTECT(metname = Rf_allocVector(STRSXP, nsp)); - PROTECT(metcomp = Rf_allocVector(STRSXP, nsp)); - PROTECT(metcharge = Rf_allocVector(INTSXP, nsp)); - PROTECT(metchemic = Rf_allocVector(STRSXP, nsp)); - PROTECT(metbndcnd = Rf_allocVector(LGLSXP, nsp)); - PROTECT(metannot = Rf_allocVector(STRSXP, nsp)); - PROTECT(metnotes = Rf_allocVector(STRSXP, nsp)); - - int chcount=0; - int notescount=0; - int annotcount=0; - - for (i = 0; i < nsp; i++) { - /* splel = (Species_t *) ListOf_get(spl, i); */ - splel = Model_getSpecies(R_ExternalPtrAddr(sbmlmod), i); - /* id */ - if (Species_isSetId(splel)) { - SET_STRING_ELT(metid, i, Rf_mkChar(Species_getId(splel))); - } - else { - SET_STRING_ELT(metid, i, Rf_mkChar("no_id")); - } - /* name */ - if (Species_isSetName(splel)) { - SET_STRING_ELT(metname, i, Rf_mkChar(Species_getName(splel))); - } - else { - SET_STRING_ELT(metname, i, Rf_mkChar("")); - } - /* compartment */ - if (Species_isSetCompartment(splel)) { - SET_STRING_ELT(metcomp, i, Rf_mkChar(Species_getCompartment(splel))); - } - else { - SET_STRING_ELT(metcomp, i, Rf_mkChar("")); - } - /* charge */ - if (Species_isSetCharge(splel)) { - INTEGER(metcharge)[i] = Species_getCharge(splel); - } - else { - INTEGER(metcharge)[i] = 0; - } - /* boundary condition */ - if (Species_isSetBoundaryCondition(splel)) { - LOGICAL(metbndcnd)[i] = Species_getBoundaryCondition(splel); - } - else { - LOGICAL(metbndcnd)[i] = 0; - } - - - - /* notes */ - if (SBase_isSetNotes((SBase_t *) splel)) { - SET_STRING_ELT(metnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) splel))); - notescount=notescount+1; - - } - else { - SET_STRING_ELT(metnotes, i, Rf_mkChar("")); - } - - /* annotation */ - if (SBase_isSetAnnotation((SBase_t *) splel)) { - //SET_STRING_ELT(metannot, i, Rf_mkChar(SBase_getAnnotationString((SBase_t *) splel))); - XMLNode_t* xml = SBase_getAnnotation((SBase_t *) splel); - annotcount=annotcount+1; - SET_STRING_ELT(metannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); - } - else { - SET_STRING_ELT(metannot, i, Rf_mkChar("")); - } - - - /* FBC PLUGIN @ Ardalan */ - SBasePlugin_t *SpeciesPlug = SBase_getPlugin((SBase_t *)(splel), "fbc"); - - /* FBCcharge */ - if (FbcSpeciesPlugin_isSetCharge(SpeciesPlug)) { - INTEGER(metcharge)[i] = FbcSpeciesPlugin_getCharge(SpeciesPlug); - } - - /* FBC chemicalFormula */ - if (FbcSpeciesPlugin_isSetChemicalFormula(SpeciesPlug)) { - SET_STRING_ELT(metchemic, i, Rf_mkChar(FbcSpeciesPlugin_getChemicalFormula(SpeciesPlug))); - chcount=chcount+1; - } - else { - SET_STRING_ELT(metchemic, i, Rf_mkChar("")); - } - - - } - - // NULL if empty - if (chcount==0) metchemic = R_NilValue; - if (notescount==0) metnotes = R_NilValue; - if (annotcount==0) metannot = R_NilValue; - - PROTECT(out = Rf_allocVector(VECSXP, 8)); - SET_VECTOR_ELT(out, 0, metid); - SET_VECTOR_ELT(out, 1, metname); - SET_VECTOR_ELT(out, 2, metcomp); - SET_VECTOR_ELT(out, 3, metcharge); - SET_VECTOR_ELT(out, 4, metchemic); - SET_VECTOR_ELT(out, 5, metbndcnd); - SET_VECTOR_ELT(out, 6, metannot); - SET_VECTOR_ELT(out, 7, metnotes); - - - PROTECT(listv = Rf_allocVector(STRSXP, 8)); - SET_STRING_ELT(listv, 0, Rf_mkChar("id")); - SET_STRING_ELT(listv, 1, Rf_mkChar("name")); - SET_STRING_ELT(listv, 2, Rf_mkChar("compartment")); - SET_STRING_ELT(listv, 3, Rf_mkChar("charge")); - SET_STRING_ELT(listv, 4, Rf_mkChar("chemicalFormula")); - SET_STRING_ELT(listv, 5, Rf_mkChar("boundaryCondition")); - SET_STRING_ELT(listv, 6, Rf_mkChar("annotation")); - SET_STRING_ELT(listv, 7, Rf_mkChar("notes")); - - - Rf_setAttrib(out, R_NamesSymbol, listv); - - /* make the list to be an instance of 'species_list' */ - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("species_list")); - Rf_classgets(out, class); - - UNPROTECT(11); - } - else { - out = R_NilValue; - } - - return out; -} - - -SEXP getSBMLGroupsList(SEXP sbmlmod) { - GroupsModelPlugin_t * modelPlug = NULL; - modelPlug = (GroupsModelPlugin_t *) SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmlmod)), "groups"); - - if(modelPlug != NULL){ - int n = GroupsModelPlugin_getNumGroups(modelPlug); - SEXP rgroups = PROTECT(Rf_allocVector(VECSXP, n)); - SEXP groupnames = PROTECT(Rf_allocVector(STRSXP, n)); - for(int i=0; i<n; i++){ - Group_t* group = GroupsModelPlugin_getGroup(modelPlug, i); - if(Group_isSetName(group) == 1){ // skip group if no name is set - SET_STRING_ELT(groupnames, i, Rf_mkChar(Group_getName(group))); - - int m = Group_getNumMembers(group); - SEXP rmembers = PROTECT(Rf_allocVector(STRSXP, m)); - for(int j=0; j < m; j++){ - Member_t * member = Group_getMember(group, j); - char * memref = Member_getIdRef(member); - SET_STRING_ELT(rmembers, j, Rf_mkChar(memref)); - } - SET_VECTOR_ELT(rgroups, i, rmembers); - UNPROTECT(1); - }else{ - SET_VECTOR_ELT(rgroups, i, R_NilValue); - } - } - Rf_namesgets(rgroups, groupnames); - UNPROTECT(2); - return rgroups; - }else{ - return R_NilValue; - } - return R_NilValue; -} - -/* -------------------------------------------------------------------------- */ -/* get list of reactions */ -SEXP getSBMLReactionsList(SEXP sbmlmod) { - - SEXP out = R_NilValue; - SEXP class = R_NilValue; - SEXP listv = R_NilValue; - SEXP reactid = R_NilValue; - SEXP reactname = R_NilValue; - SEXP reactrev = R_NilValue; - SEXP reactnotes = R_NilValue; - SEXP reactannot = R_NilValue; - SEXP reactreact = R_NilValue; - SEXP reactprod = R_NilValue; - SEXP reactkl = R_NilValue; - - SEXP parml = R_NilValue; - SEXP parmn = R_NilValue; - SEXP parmid = R_NilValue; - SEXP parmval = R_NilValue; - SEXP parmunit = R_NilValue; - - SEXP fbclb = R_NilValue; //lowerbnd - SEXP fbcup = R_NilValue; //upperbnd - SEXP fbcgene = R_NilValue; //fbc gene Rules - SEXP fbcobj = R_NilValue; // fbc objective - - unsigned int nre, i, j, nreactant, nproduct, nparm; - - /* ListOf_t *rel; */ - Reaction_t *relel; - KineticLaw_t *kl; - Parameter_t *parm; - - checkModel(sbmlmod); - - /* rel = Model_getListOfReactions(R_ExternalPtrAddr(sbmlmod)); */ - nre = Model_getNumReactions(R_ExternalPtrAddr(sbmlmod)); - - if (nre > 0) { - PROTECT(reactid = Rf_allocVector(STRSXP, nre)); - PROTECT(reactname = Rf_allocVector(STRSXP, nre)); - PROTECT(reactrev = Rf_allocVector(LGLSXP, nre)); - PROTECT(reactnotes = Rf_allocVector(STRSXP, nre)); - PROTECT(reactannot = Rf_allocVector(STRSXP, nre)); - PROTECT(reactreact = Rf_allocVector(VECSXP, nre)); - PROTECT(reactprod = Rf_allocVector(VECSXP, nre)); - PROTECT(reactkl = Rf_allocVector(VECSXP, nre)); - - PROTECT(fbclb = Rf_allocVector(REALSXP, nre)); - PROTECT(fbcup = Rf_allocVector(REALSXP, nre)); - PROTECT(fbcgene = Rf_allocVector(STRSXP , nre)); - PROTECT(fbcobj = Rf_allocVector(REALSXP, nre)); - - - int lbcount=0; - int upcount=0; - int genecount=0; - int objcount=0; - int annocount=0; - int notescount=0; - - /* Help Var for Fbc Objective*/ - double Objcoeff =0; - const char* Objreaction = NULL; - char* objActiv = NULL; - int fbcversion = 0; - - /* FBC OBJECTIV @Ardalan*/ - Objective_t * objective; - FluxObjective_t * fluxObjective; - SBasePlugin_t * modelPlug= NULL; - - modelPlug = SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmlmod)), "fbc"); - - // Read the Objectives when FBCPlugin for the model exists - if( modelPlug != NULL) - { - - objActiv = FbcModelPlugin_getActiveObjectiveId(modelPlug); - int ob=0; - if(strcmp(objActiv,"") !=0) - { - for(ob; ob< FbcModelPlugin_getNumObjectives(modelPlug);ob++) - { - objective= FbcModelPlugin_getObjective(modelPlug,ob); - //printf("ObjectiveID: %s \n", Objective_getId(objective) ); - if(strcmp(objActiv,Objective_getId(objective))==0) - { // TODO mehrer FLUXOBJECTIVE; MAXimierung Minimirung? - - // int fob=0; - // for(fob; ob<FbcModelPlugin_getNumObjectives(modelPlug);fob++ ) - // { - fluxObjective= Objective_getFluxObjective(objective,0); - Objreaction= FluxObjective_getReaction(fluxObjective) ; - Objcoeff = FluxObjective_getCoefficient(fluxObjective); - - //printf("ReactionObjectiveID: %s \n", Objreaction); - //printf("Coefficient: %f \n", Objcoeff); - // } - } - - } - - } - - - /* is FBC 1 */ - - if(strcmp("fbc",SBasePlugin_getPackageName(modelPlug) ) ==0) - fbcversion = SBasePlugin_getPackageVersion(modelPlug); - } - - - for (i = 0; i < nre; i++) { - /* relel = (Reaction_t *) ListOf_get(rel, i); */ - relel = Model_getReaction(R_ExternalPtrAddr(sbmlmod), i); - - nreactant = Reaction_getNumReactants(relel); - nproduct = Reaction_getNumProducts(relel); - - /* id */ - if (Reaction_isSetId(relel)) { - SET_STRING_ELT(reactid, i, Rf_mkChar(Reaction_getId(relel))); - } - else { - SET_STRING_ELT(reactid, i, Rf_mkChar("no_id")); - } - /* name */ - if (Reaction_isSetName(relel)) { - SET_STRING_ELT(reactname, i, Rf_mkChar(Reaction_getName(relel))); - } - else { - SET_STRING_ELT(reactname, i, Rf_mkChar("")); - } - /* reversible */ - if (Reaction_isSetReversible(relel)) { - LOGICAL(reactrev)[i] = Reaction_getReversible(relel); - } - else { - LOGICAL(reactrev)[i] = 0; - } - /* notes */ - if (SBase_isSetNotes((SBase_t *) relel)) { - SET_STRING_ELT(reactnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) relel))); - notescount=notescount+1; - } - else { - SET_STRING_ELT(reactnotes, i, Rf_mkChar("")); - } - /* annotation */ - if (SBase_isSetAnnotation((SBase_t *) relel)) { - //SET_STRING_ELT(reactannot, i, Rf_mkChar(SBase_getAnnotationString((SBase_t *) relel))); - XMLNode_t* xml = SBase_getAnnotation((SBase_t *) relel); - SET_STRING_ELT(reactannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); - annocount=annocount+1; - } - else { - SET_STRING_ELT(reactannot, i, Rf_mkChar("")); - } - - /* FBC LEVEL 2 @Ardalan Habil*/ - - /* ReactionPLugin for FBC 2 */ - SBasePlugin_t *reactionPlug = SBase_getPlugin((SBase_t *)(relel), "fbc"); - - - /* LOWERFLUXBOUND */ - if (FbcReactionPlugin_isSetLowerFluxBound(reactionPlug)) - { - parm = Model_getParameterById(R_ExternalPtrAddr (sbmlmod) ,FbcReactionPlugin_getLowerFluxBound(reactionPlug)); - //printf("LowerFLUXBOUND: %f \n", Parameter_getValue(parm)); - REAL(fbclb)[i] = Parameter_getValue(parm); - lbcount=lbcount+1; - } - else{ - REAL(fbclb)[i] = 0; - } - - /* UPPERFLUXBOUND*/ - if (FbcReactionPlugin_isSetUpperFluxBound(reactionPlug)) - { - parm = Model_getParameterById(R_ExternalPtrAddr (sbmlmod) ,FbcReactionPlugin_getUpperFluxBound(reactionPlug)); - //printf("UPPERFLUXBOUND: %f \n", Parameter_getValue(parm)); - REAL(fbcup)[i] = Parameter_getValue(parm); - upcount=upcount+1; - } - else{ - REAL(fbcup)[i] = 0; - } - - /*FBC 1 read */ - if (fbcversion==1) - { - /* Storing FBC1Bounds */ - double fbc1lb=0; - double fbc1up=0; - - - int fluxb=0; - for(fluxb; fluxb< FbcModelPlugin_getNumFluxBounds(modelPlug);fluxb++) - { - FluxBound_t * currentFlux = FbcModelPlugin_getFluxBound(modelPlug,fluxb); - - const char * currentFluxType ; - const char * currentFluxReaction; - - if (FluxBound_isSetReaction(currentFlux)) currentFluxReaction = FluxBound_getReaction(currentFlux); - else continue; - - if(strcmp(currentFluxReaction , Reaction_getId(relel) ) !=0) continue; - - - if (FluxBound_isSetOperation(currentFlux)) currentFluxType = FluxBound_getOperation(currentFlux); - else continue; - - - if(strcmp("greaterEqual" , currentFluxType ) ==0) - { - lbcount=lbcount+1; - if (FluxBound_isSetValue(currentFlux)) fbc1lb = FluxBound_getValue(currentFlux); - else continue; - } - - else if(strcmp("lessEqual" , currentFluxType ) ==0) - { - upcount=upcount+1; - if (FluxBound_isSetValue(currentFlux)) fbc1up = FluxBound_getValue(currentFlux); - else continue; - } - - else if(strcmp("equal" , currentFluxType ) ==0) - { - if (FluxBound_isSetValue(currentFlux)) - { - lbcount=lbcount+1; - upcount=upcount+1; - fbc1lb = FluxBound_getValue(currentFlux); - fbc1up = FluxBound_getValue(currentFlux); - } - else continue; - } - - } - - /* FBC 1 save Bounds */ - REAL(fbclb)[i] = fbc1lb; - REAL(fbcup)[i] = fbc1up; - - } - - - /* FBC GENE */ - if( FbcReactionPlugin_isSetGeneProductAssociation(reactionPlug) ) { - GeneProductAssociation_t* gpa = FbcReactionPlugin_getGeneProductAssociation(reactionPlug); - FbcAssociation_t* asso= (FbcAssociation_t*) GeneProductAssociation_getAssociation(gpa); - SET_STRING_ELT(fbcgene, i, Rf_mkChar(FbcAssociation_toInfix(asso))); - //printf("Gene: %s \n", FbcAssociation_toInfix(asso)); - genecount=genecount+1; - } - else { - SET_STRING_ELT(fbcgene, i, Rf_mkChar("")); - } - - /* FBC OBJECTIVES*/ - if (Objreaction != NULL && strcmp(Objreaction , Reaction_getId(relel) )==0) - { - - REAL(fbcobj)[i] = Objcoeff; - objcount=objcount+1; - } - else{ - REAL(fbcobj)[i] = 0; - } - - - /* reactants */ - SET_VECTOR_ELT(reactreact, i, getSpeciesReference(relel, nreactant, 0)); - - /* products */ - SET_VECTOR_ELT(reactprod, i, getSpeciesReference(relel, nproduct, 1)); - - /* kineticLaw */ - if (Reaction_isSetKineticLaw(relel)) { - kl = Reaction_getKineticLaw(relel); - nparm = KineticLaw_getNumParameters(kl); - - if (nparm > 0) { - PROTECT(parmid = Rf_allocVector(STRSXP, nparm)); - PROTECT(parmval = Rf_allocVector(REALSXP, nparm)); - PROTECT(parmunit = Rf_allocVector(STRSXP, nparm)); - - for (j = 0; j < nparm; j++) { - parm = KineticLaw_getParameter(kl, j); - - /* id */ - if (Parameter_isSetId(parm)) { - SET_STRING_ELT(parmid, j, Rf_mkChar(Parameter_getId(parm))); - } - else { - SET_STRING_ELT(parmid, j, Rf_mkChar("no_id")); - } - /* value */ - if (Parameter_isSetValue(parm)) { - REAL(parmval)[j] = Parameter_getValue(parm); - } - else { - REAL(parmval)[j] = 0; - } - /* units */ - if (Parameter_isSetUnits(parm)) { - SET_STRING_ELT(parmunit, j, Rf_mkChar(Parameter_getUnits(parm))); - } - else { - SET_STRING_ELT(parmunit, j, Rf_mkChar("")); - } - } - - PROTECT(parml = Rf_allocVector(VECSXP, 3)); - SET_VECTOR_ELT(parml, 0, parmid); - SET_VECTOR_ELT(parml, 1, parmval); - SET_VECTOR_ELT(parml, 2, parmunit); - - PROTECT(parmn = Rf_allocVector(STRSXP, 3)); - SET_STRING_ELT(parmn, 0, Rf_mkChar("id")); - SET_STRING_ELT(parmn, 1, Rf_mkChar("value")); - SET_STRING_ELT(parmn, 2, Rf_mkChar("units")); - Rf_setAttrib(parml, R_NamesSymbol, parmn); - - UNPROTECT(5); - } - else { - parml = R_NilValue; - } - SET_VECTOR_ELT(reactkl, i, parml); - } - else { - SET_VECTOR_ELT(reactkl, i, R_NilValue); - } - - - } - - // NULL if empty - if(lbcount==0) fbclb = R_NilValue; - if(upcount==0) fbcup = R_NilValue; - if(genecount==0) fbcgene = R_NilValue; - if(objcount==0) fbcobj = R_NilValue; - if(annocount==0) reactannot= R_NilValue; - if(notescount==0) reactnotes= R_NilValue; - - - PROTECT(out = Rf_allocVector(VECSXP, 12)); - SET_VECTOR_ELT(out, 0, reactid); - SET_VECTOR_ELT(out, 1, reactname); - SET_VECTOR_ELT(out, 2, reactrev); - SET_VECTOR_ELT(out, 3, reactnotes); - SET_VECTOR_ELT(out, 4, reactannot); - SET_VECTOR_ELT(out, 5, reactreact); - SET_VECTOR_ELT(out, 6, reactprod); - SET_VECTOR_ELT(out, 7, reactkl); - SET_VECTOR_ELT(out, 8, fbclb); - SET_VECTOR_ELT(out, 9, fbcup); - SET_VECTOR_ELT(out, 10, fbcgene); - SET_VECTOR_ELT(out, 11, fbcobj); - - - PROTECT(listv = Rf_allocVector(STRSXP, 12)); - SET_STRING_ELT(listv, 0, Rf_mkChar("id")); - SET_STRING_ELT(listv, 1, Rf_mkChar("name")); - SET_STRING_ELT(listv, 2, Rf_mkChar("reversible")); - SET_STRING_ELT(listv, 3, Rf_mkChar("notes")); - SET_STRING_ELT(listv, 4, Rf_mkChar("annotation")); - SET_STRING_ELT(listv, 5, Rf_mkChar("reactants")); - SET_STRING_ELT(listv, 6, Rf_mkChar("products")); - SET_STRING_ELT(listv, 7, Rf_mkChar("kinetic_law")); - SET_STRING_ELT(listv, 8, Rf_mkChar("fbc_lowbnd")); - SET_STRING_ELT(listv, 9, Rf_mkChar("fbc_uppbnd")); - SET_STRING_ELT(listv, 10, Rf_mkChar("fbc_gprRules")); - SET_STRING_ELT(listv, 11, Rf_mkChar("fbc_Objectives")); - - Rf_setAttrib(out, R_NamesSymbol, listv); - - /* make the list to be an instance of 'reactions_list' */ - PROTECT(class = Rf_allocVector(STRSXP, 1)); - SET_STRING_ELT(class, 0, Rf_mkChar("reactions_list")); - Rf_classgets(out, class); - - UNPROTECT(15); - } - else { - out = R_NilValue; - } - - return out; -} - -/* -------------------------------------------------------------------------- */ -/* export SBML*/ - -void ParseModtoAnno (SBase_t* comp , char* Mannocopy) - -{ - - char delimiter[] = ";"; - char *ptr; - ptr = strtok(Mannocopy, delimiter); - char* quali; - CVTerm_t *cv; - int first=0; - - while(ptr != NULL) { - - if(strncmp("bqbiol", ptr, strlen("bqbiol")) == 0) - { - if (first != 0){ SBase_addCVTerm((SBase_t*)comp, cv);CVTerm_free(cv);} - //CVTerm_free(cv); - quali = strcpy(&ptr[0],&ptr[7]); - cv = CVTerm_createWithQualifierType(BIOLOGICAL_QUALIFIER); - CVTerm_setBiologicalQualifierTypeByString( cv, (const char*) quali); - first=1; - } - else if(strncmp("bqmodel", ptr, strlen("bqmodel")) == 0) - { - if (first != 0) { SBase_addCVTerm((SBase_t*)comp, cv);CVTerm_free(cv);} - //CVTerm_free(cv); - quali = strcpy(&ptr[0],&ptr[8]); - cv = CVTerm_createWithQualifierType(MODEL_QUALIFIER); - CVTerm_setModelQualifierTypeByString( cv, (const char*) quali); - } - else - { - CVTerm_addResource(cv,ptr ); - } - - // naechsten Abschnitt erstellen - ptr = strtok(NULL, delimiter); - } - SBase_addCVTerm((SBase_t*)comp, cv); - -} - - - -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 subSysGroups, 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) -{ - //Varaibles from R - const char* fname = CHAR(STRING_ELT(filename, 0)); - const char* model_desc = CHAR(STRING_ELT(mod_desc, 0)); - const char* model_name = CHAR(STRING_ELT(mod_name, 0)); - - int SBMLlevel = INTEGER(level)[0]; - int SBMLversion = INTEGER(version)[0]; - int SBMLfbcversion = INTEGER(FbcLevel)[0]; - int SBMLgroupsversion = 1; - double sybilmax = REAL(sybil_max)[0]; - double sybilmin = sybilmax*(-1); - - // variable FBC - XMLNamespaces_t * fbc; - SBMLNamespaces_t * sbmlns; - FluxBound_t * fluxBound; - Objective_t * objective; - FluxObjective_t * fluxObjective; - SBMLDocumentPlugin_t * docPlug; - SBasePlugin_t * modelPlug; - SBasePlugin_t *reactionPlug; - SBasePlugin_t *SpeciesPlug ; - - FbcAssociation_t* asso; - - - // Variable inital - - SBMLDocument_t* sbmlDoc; - Model_t* model; - XMLNamespaces_t* xmlns; - - UnitDefinition_t* unitdef; - Unit_t* unit; - - Species_t *sp; - Reaction_t* reaction; - SpeciesReference_t* spr; - Compartment_t* comp; - KineticLaw_t* kl; - Parameter_t* para; - - // ASTNode_t* flux; - ASTNode_t* astMath; - //ASTNode_t* ast; - //char* mathXMLString; - - /*--------------------------------------------------------------------------- - * - * Creates an SBMLDocument object - * - *---------------------------------------------------------------------------*/ - - if (SBMLlevel == 1 || SBMLlevel == 2) - { - sbmlDoc = SBMLDocument_createWithLevelAndVersion(SBMLlevel,SBMLversion); - xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); - XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); - } - else if(SBMLlevel == 3) - { - if(SBMLfbcversion == 0) - { - sbmlDoc = SBMLDocument_createWithLevelAndVersion(3,1); - xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); - XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); - - } else { - - /* FBC LEVEL */ - /* get fbc registry entry */ - SBMLExtension_t *sbmlext = SBMLExtensionRegistry_getExtension("fbc"); - - /* create the sbml namespaces object with fbc */ - XMLNamespaces_t * fbc = XMLNamespaces_create(); - XMLNamespaces_add(fbc, SBMLExtension_getURI(sbmlext, 3, 1, SBMLfbcversion), "fbc"); - - sbmlns = SBMLNamespaces_create(3, 1); - SBMLNamespaces_addNamespaces(sbmlns, fbc); - - /* add groups extention */ - SBMLExtension_t *sbmlgext = SBMLExtensionRegistry_getExtension("groups"); - XMLNamespaces_t * groups = XMLNamespaces_create(); - XMLNamespaces_add(groups, SBMLExtension_getURI(sbmlgext, SBMLlevel, SBMLversion, SBMLgroupsversion), "groups"); - SBMLNamespaces_addNamespaces(sbmlns, groups); - - /* create the document */ - sbmlDoc = SBMLDocument_createWithSBMLNamespaces(sbmlns); - - /* XHTML for notes*/ - xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); - XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); - - /* set the fbc reqd attribute to false */ - docPlug = (SBMLDocumentPlugin_t*)(SBase_getPlugin((SBase_t*)(sbmlDoc), "fbc")); - SBMLDocumentPlugin_setRequired(docPlug, 0); - - } - - } - - - /*--------------------------------------------------------------------------- - * - * Creates a Model object inside the SBMLDocument object. - * - *---------------------------------------------------------------------------*/ - - model = SBMLDocument_createModel(sbmlDoc); - Model_setId(model,model_name); - - // Get a SBasePlugin_t object plugged in the model object. - if(SBMLfbcversion == 2) - { - modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); - - // set the fbc strict attribute - FbcModelPlugin_setStrict(modelPlug, 1); - } - - // Model NOTERS - if (!Rf_isNull(mod_notes)) - { - char *Modnotes = (char*) CHAR(STRING_ELT(mod_notes, 0)); - if ((Modnotes != NULL) && (Modnotes[0] != '\0')) - { - //printf("Canno: %s", Cnotes); - SBase_setNotesString((SBase_t*) model , Modnotes); - } - } - - /*Annotation*/ - if (!Rf_isNull(mod_anno) ) - { char *Manno = (char*) CHAR(STRING_ELT(mod_anno, 0)); - if((Manno != NULL) && (Manno[0] != '\0' )) - { - SBase_setMetaId((SBase_t*)model,model_name); - char Mannocopy[strlen(Manno)+1]; - strcpy(Mannocopy,Manno); - // PARSING - ParseModtoAnno((SBase_t*)model, Mannocopy); - - } - } - - /*--------------------------------------------------------------------------- - * - * Creates UnitDefinition objects inside the Model object. - * - *---------------------------------------------------------------------------*/ - /* - unitdef = Model_createUnitDefinition(model); - UnitDefinition_setId(unitdef,"litre_per_mole_per_second"); - - // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") - - unit = UnitDefinition_createUnit(unitdef); - Unit_setKind(unit,UNIT_KIND_MOLE); - Unit_setExponent(unit,-1); - - // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") - - unit = UnitDefinition_createUnit(unitdef); - Unit_setKind(unit,UNIT_KIND_LITRE); - Unit_setExponent(unit,1); - - // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") - - unit = UnitDefinition_createUnit(unitdef); - Unit_setKind(unit,UNIT_KIND_SECOND); - Unit_setExponent(unit,-1); - - */ - - /*--------------------------------------------------------------------------- - * - * Creates a Compartment object inside the Model object. - * - *---------------------------------------------------------------------------*/ - - const char *sName; - int i; - int hasBoundary=0; - for (i=0; i<LENGTH(mod_compart); i++) - { - sName = CHAR(STRING_ELT(mod_compart, i)); - comp = Model_createCompartment(model); - Compartment_setId(comp,sName); - Compartment_setConstant(comp,1); - if( strcmp(sName,"BOUNDARY")==0 || strcmp(sName,"Boundary")==0 || strcmp(sName,"boundary")==0)hasBoundary=1; - if (!Rf_isNull(com_notes) && Rf_length(com_notes) > 1) - { - char *Cnotes = (char*) CHAR(STRING_ELT(com_notes, i)); - if ((Cnotes != NULL) && (Cnotes[0] != '\0')) - { - //printf("Canno: %s", Cnotes); - SBase_setNotesString((SBase_t*)comp, Cnotes); - } - } - - - if (!Rf_isNull(com_anno) && Rf_length(com_anno) > 1 ) - { char *Manno = (char*) CHAR(STRING_ELT(com_anno, i)); - if((Manno != NULL) && (Manno[0] != '\0' )) - { - SBase_setMetaId((SBase_t*)comp, CHAR(STRING_ELT(mod_compart, i))); - char Mannocopy[strlen(Manno)+1]; - strcpy(Mannocopy,Manno); - ParseModtoAnno((SBase_t*) comp,Mannocopy); - - } - } - - } - - - /* Boundary Compartment */ - if(hasBoundary==0 && Rf_isNull(met_bnd) && Rf_length(met_bnd) <= 1 && !Rf_isNull(ex_react)) - { - comp = Model_createCompartment(model); - Compartment_setId(comp,"BOUNDARY"); - Compartment_setConstant(comp,1); - hasBoundary=1; - } - /*--------------------------------------------------------------------------- - * - * Creates Species objects inside the Model object. - * - *---------------------------------------------------------------------------*/ - for (i=0; i<LENGTH(met_name); i++) - { - - - sp = Model_createSpecies(model); - Species_setId(sp,CHAR(STRING_ELT(met_id, i))); - Species_setName(sp,CHAR(STRING_ELT(met_name, i))); - Species_setCompartment(sp,CHAR(STRING_ELT(met_comp, i))); - Species_setHasOnlySubstanceUnits(sp, 0); - Species_setConstant(sp, 0); - - //Bondary Condition - if (!Rf_isNull(met_bnd) && Rf_length(met_bnd) > 1) Species_setBoundaryCondition(sp, LOGICAL(met_bnd)[i]); - else Species_setBoundaryCondition(sp, 0); - - - int hasNotes=0; - const char* metnote=""; - if (!Rf_isNull(met_form) && Rf_length(met_form) > 1) - { - if (SBMLfbcversion >0) - { - SpeciesPlug = SBase_getPlugin((SBase_t *)(sp), "fbc"); - FbcSpeciesPlugin_setChemicalFormula(SpeciesPlug, CHAR(STRING_ELT(met_form, i))); - } - - else{ - metnote = append_strings(metnote,"<html:p>FORMULA: ",""); - metnote =append_strings(metnote,CHAR(STRING_ELT(met_form, i)),""); - metnote =append_strings(metnote," </html:p>",""); - hasNotes=1; - } - } - - if (!Rf_isNull(met_charge) && Rf_length(met_charge) > 1) - { - if (SBMLfbcversion >0) - { - SpeciesPlug = SBase_getPlugin((SBase_t *)(sp), "fbc"); - FbcSpeciesPlugin_setCharge(SpeciesPlug, INTEGER(met_charge)[i]); - } - else - { - metnote = append_strings(metnote,"<html:p>CHARGE: ",""); - char chint[256]; - sprintf(chint, "%d", INTEGER(met_charge)[i]); - metnote =append_strings(metnote,chint,""); - metnote =append_strings(metnote," </html:p>",""); - hasNotes=1; - } - } - - - if (!Rf_isNull(met_notes) && Rf_length(met_notes) > 1) - { - char *Mnotes = (char*) CHAR(STRING_ELT(met_notes, i)); - if ((Mnotes != NULL) && (Mnotes[0] != '\0')) - { - SBase_setNotesString((SBase_t*)sp, Mnotes); - hasNotes=0; - } - - } - - - if(hasNotes !=0 )SBase_setNotesString((SBase_t*)sp, metnote); - - if (!Rf_isNull(met_anno) && Rf_length(met_anno) > 1 ) - { char *Manno = (char*) CHAR(STRING_ELT(met_anno, i)); - - if((Manno != NULL) && (Manno[0] != '\0' )) - { - - SBase_setMetaId((SBase_t*)sp, CHAR(STRING_ELT(met_id, i))); - - // COPY STRING - char *Manno = (char*) CHAR(STRING_ELT(met_anno, i)); - char Mannocopy[strlen(Manno)+1]; - strcpy(Mannocopy,Manno); - // PARSING - ParseModtoAnno((SBase_t*)sp, Mannocopy); - - } - } - - - - } - /*--------------------------------------------------------------------------- - * - * Creates Reaction objects inside the Model object. - * - *---------------------------------------------------------------------------*/ - - /* LISTOFGENES - * - */ - if(SBMLfbcversion == 2 && Rf_length(gpr) > 1) - { - if (!Rf_isNull(gpr) && Rf_length(gpr) > 1) - { - modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); - //GeneProduct_t* gene; - char* genid = malloc( 100 ); - - for (i=0; i<LENGTH(allgenes); i++) - { - GeneProduct_t* gene = GeneProduct_create(3,1,2); - sprintf(genid,"G_%s", CHAR(STRING_ELT(allgenes, i))); - GeneProduct_setId(gene ,genid); - GeneProduct_setLabel(gene ,CHAR(STRING_ELT(allgenes, i))); - FbcModelPlugin_addGeneProduct(modelPlug,gene); - } - free(genid); - } - /* - ListOfParemters - */ - - // create the Parameters - - para = Model_createParameter(model); - Parameter_setId(para, "default_lb"); - Parameter_setConstant(para, 1); - Parameter_setValue(para, sybilmin); - SBase_setSBOTerm((SBase_t *)para,626); - - para = Model_createParameter(model); - Parameter_setId(para, "default_ub"); - Parameter_setConstant(para, 1); - Parameter_setValue(para, sybilmax); - SBase_setSBOTerm((SBase_t *)para,626); - - para = Model_createParameter(model); - Parameter_setId(para, "default_0"); - Parameter_setConstant(para, 1); - Parameter_setValue(para, 0); - SBase_setSBOTerm((SBase_t *)para,626); - - } - - - // LOOP FOR REACTION - for (i=0; i<LENGTH(react_name); i++) - { - reaction = Model_createReaction(model); - - Reaction_setId(reaction, CHAR(STRING_ELT(react_id, i))); - Reaction_setName(reaction, CHAR(STRING_ELT(react_name, i))); - Reaction_setReversible(reaction,LOGICAL(react_rev)[i]); - Reaction_setFast(reaction, 0); - - if(SBMLfbcversion == 2) - { - // FBCv2 - reactionPlug = SBase_getPlugin((SBase_t *)(reaction), "fbc"); - GeneProductAssociation_t* gpa = GeneProductAssociation_create(3,1,2); - - // FbcAnd_t * und= FbcAnd_create(3,1,2); - asso= FbcAssociation_parseFbcInfixAssociation(CHAR(STRING_ELT(gpr, i)),modelPlug); - GeneProductAssociation_setAssociation(gpa,asso); - FbcReactionPlugin_setGeneProductAssociation(reactionPlug,gpa); - } - - - - const char* notesString = ""; - - - - if (!Rf_isNull(react_notes) && Rf_length(react_notes) > 1) - { - char *Rnotes = (char*) CHAR(STRING_ELT(react_notes, i)); - if ((Rnotes != NULL) && (Rnotes[0] != '\0')) - { - //printf("Reaction Nores:%s ",Rnotes); - SBase_setNotesString((SBase_t*)reaction, Rnotes); - } - - } - else - { - if(SBMLfbcversion == 0) - { - if (!Rf_isNull(gpr) && Rf_length(gpr) > 1) - { - notesString = append_strings(notesString,"<html:p>GENE_ASSOCIATION: ",""); - notesString =append_strings(notesString,CHAR(STRING_ELT(gpr, i)),""); - notesString =append_strings(notesString," </html:p>",""); - } - if (!Rf_isNull(subSys) && Rf_length(subSys) > 1) - { - notesString = append_strings(notesString,"<html:p>SUBSYSTEM: ",""); - notesString =append_strings(notesString,CHAR(STRING_ELT(subSys, i)),""); - notesString =append_strings(notesString," </html:p>",""); - } - - SBase_setNotesString((SBase_t*)reaction, notesString); - } - } - - const double *lower_bnd = REAL(lowbnd); - const double *upper_bnd = REAL(uppbnd); - - // KineticLaw - if(SBMLfbcversion == 0) - { - kl = Reaction_createKineticLaw(reaction); - - astMath = ASTNode_createWithType(AST_NAME); - ASTNode_setName(astMath, "FLUX_VALUE"); - - KineticLaw_setMath( kl, astMath); - - - para = KineticLaw_createParameter( kl ); - Parameter_setId(para, "LOWER_BOUND"); - Parameter_setValue( para, lower_bnd[i]); - //Parameter_setUnits( para, "litre_per_mole_per_second"); - - para = KineticLaw_createParameter( kl ); - Parameter_setId(para, "UPPER_BOUND"); - Parameter_setValue( para, upper_bnd[i]); - //Parameter_setUnits( para, "litre_per_mole_per_second"); - - para = KineticLaw_createParameter( kl ); - Parameter_setId(para, "OBJECTIVE_COEFFICIENT"); - Parameter_setValue( para, INTEGER(obj_coef)[i]); - - para = KineticLaw_createParameter( kl ); - Parameter_setId(para, "FLUX_VALUE"); - Parameter_setValue( para, 0); - } - - - int isexchange=0; - int k; - if (Rf_isNull(met_bnd) && Rf_length(met_bnd) <= 1 && !Rf_isNull(ex_react)) - for (k=0; k<LENGTH(ex_react); k++) - if( i+1 == INTEGER(ex_react)[k]) - isexchange=1; - - int j=0; - for (j=0; j<LENGTH(met_id); j++) - { - - int hash = LENGTH(met_id) * i + j; - if (REAL(SMatrix)[hash] != 0.00 ) - { - - if(REAL(SMatrix)[hash] < 0.00) - { - spr = Reaction_createReactant(reaction); - SpeciesReference_setConstant(spr, 1); - SpeciesReference_setSpecies(spr,CHAR(STRING_ELT(met_id, j))); - SpeciesReference_setStoichiometry(spr, fabs(REAL(SMatrix)[hash])); - - //is Exchange Reaction - if(isexchange==1 && !Rf_isNull(ex_react)) - { - /* Create boundary Species */ - sp = Model_createSpecies(model); - - Species_setId(sp, append_strings(CHAR(STRING_ELT(met_id, j)),"BOUNDARY","_") ); - Species_setName(sp,append_strings(CHAR(STRING_ELT(met_name, j)),"BOUNDARY"," ") ); - - Species_setCompartment(sp,"BOUNDARY"); - Species_setHasOnlySubstanceUnits(sp, 0); - Species_setBoundaryCondition(sp, 1); - Species_setConstant(sp, 1); - - /* Add boundary Species as Product */ - spr = Reaction_createProduct(reaction); - SpeciesReference_setSpecies(spr,append_strings(CHAR(STRING_ELT(met_id, j)),"BOUNDARY","_") ); - SpeciesReference_setStoichiometry(spr,1); - - SpeciesReference_setConstant(spr, 1); - } - - - }else{ - spr = Reaction_createProduct(reaction); - SpeciesReference_setConstant(spr, 1); - SpeciesReference_setSpecies(spr,CHAR(STRING_ELT(met_id, j))); - SpeciesReference_setStoichiometry(spr, fabs(REAL(SMatrix)[hash])); - } - - } - } - - - - /*Annotation*/ - if (!Rf_isNull(react_anno) && Rf_length(react_anno) > 1 ) - { char *Manno = (char*) CHAR(STRING_ELT(react_anno, i)); - if((Manno != NULL) && (Manno[0] != '\0' )) - { - SBase_setMetaId((SBase_t*)reaction, CHAR(STRING_ELT(react_id, i))); - char Mannocopy[strlen(Manno)+1]; - strcpy(Mannocopy,Manno); - // PARSING - ParseModtoAnno((SBase_t*)reaction, Mannocopy); - - } - } - - - - /* FBC LEVEL 2 */ - if(SBMLfbcversion == 2) - { - // Get a SBasePlugin_t object plugged in the reaction object. - - reactionPlug = SBase_getPlugin((SBase_t *)(reaction), "fbc"); - - const char* para_lb; - const char* para_ub; - - //default Parameter or new one - if (lower_bnd[i]<= sybilmin) - { - para_lb="default_lb"; - } - else if (lower_bnd[i] == 0) - { - para_lb="default_0"; - } - else - { //creacte Lower_bound Paramater - para = Model_createParameter(model); - Parameter_setId(para, append_strings(CHAR(STRING_ELT(react_id, i)),"lower_bound","_")); - Parameter_setConstant(para, 1); - Parameter_setValue(para, lower_bnd[i]); - SBase_setSBOTerm((SBase_t *)para,625); - - para_lb=append_strings(CHAR(STRING_ELT(react_id, i)),"lower_bound","_"); - - } - - if (upper_bnd[i] >= sybilmax) - { - para_ub="default_ub"; - } - - else if (upper_bnd[i] == 0) - { - para_ub="default_0"; - } - - else - { - //creacte upper_bound Paramater - para = Model_createParameter(model); - Parameter_setId(para, append_strings(CHAR(STRING_ELT(react_id, i)),"upper_bound","_")); - Parameter_setConstant(para, 1); - Parameter_setValue(para, upper_bnd[i]); - SBase_setSBOTerm((SBase_t *)para,625); - - para_ub=append_strings(CHAR(STRING_ELT(react_id, i)),"upper_bound","_"); - } - - // set the flux bounds for this reaction - FbcReactionPlugin_setLowerFluxBound(reactionPlug, para_lb); - FbcReactionPlugin_setUpperFluxBound(reactionPlug, para_ub); - - // OBJECTIVES - if (INTEGER(obj_coef)[i]!=0) - { - objective = Objective_create(3, 1, 2); - Objective_setId(objective, "obj"); - Objective_setType(objective, "maximize"); - - fluxObjective = Objective_createFluxObjective(objective); - FluxObjective_setReaction(fluxObjective, CHAR(STRING_ELT(react_id, i))); - FluxObjective_setCoefficient(fluxObjective, INTEGER(obj_coef)[i]); - - FbcModelPlugin_addObjective(modelPlug, objective); - - // mark obj1 as active objective - FbcModelPlugin_setActiveObjectiveId(modelPlug, "obj"); - - } - } - - - }// ENDE REACTION - if(SBMLfbcversion == 1) - { - - // FBC LEVEL 1 - - // Get a SBasePlugin_t object plugged in the model object. - - modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); - int ObjCounter = 0; - for (i=0; i<LENGTH(react_name); i++) - { - - const double *lower_bnd = REAL(lowbnd); - const double *upper_bnd = REAL(uppbnd); - - char buf[21]; // changed from 20 to 21 to avoid buffer overflow - // FBC1 FLUXBOUNDS - sprintf(buf, "LOWER_BOUND%d", i); - if (INTEGER(obj_coef)[i] != 1) - { - fluxBound = FluxBound_create(3, 1, 1); - FluxBound_setId(fluxBound, buf); - FluxBound_setReaction(fluxBound, CHAR(STRING_ELT(react_id, i))); - FluxBound_setOperation(fluxBound, "greaterEqual"); - FluxBound_setValue(fluxBound, lower_bnd[i]); - FbcModelPlugin_addFluxBound(modelPlug, fluxBound); - - //printf("Upper: %s\n", buf); - sprintf(buf, "UPPER_BOUND%d", i); - fluxBound = FluxBound_create(3, 1, 1); - FluxBound_setId(fluxBound, buf); - FluxBound_setReaction(fluxBound, CHAR(STRING_ELT(react_id, i))); - FluxBound_setOperation(fluxBound, "lessEqual"); - FluxBound_setValue(fluxBound, upper_bnd[i]); - - FbcModelPlugin_addFluxBound(modelPlug, fluxBound); - } - - if (INTEGER(obj_coef)[i] == 1 && ObjCounter == 0) - { - sprintf(buf, "OBJ%d", i); - objective = Objective_create(3, 1, 1); - Objective_setId(objective, buf); - Objective_setType(objective, "maximize"); - - fluxObjective = Objective_createFluxObjective(objective); - FluxObjective_setReaction(fluxObjective, CHAR(STRING_ELT(react_id, i))); - FluxObjective_setCoefficient(fluxObjective, 1); - - FbcModelPlugin_addObjective(modelPlug, objective); - FbcModelPlugin_setActiveObjectiveId(modelPlug, buf); - ObjCounter = ObjCounter +1; - } - - - - } - } - - /* add subsystem as groups if fbc is >= 2 */ - if(SBMLfbcversion >= 2){ - if(!Rf_isNull(subSysGroups)){ - GroupsModelPlugin_t* groupsPlug = NULL; - groupsPlug = (GroupsModelPlugin_t*) SBase_getPlugin((SBase_t *)(model), "groups"); - - for(int i=0; i < Rf_length(subSysGroups); i++){ - Group_t* newGroup = GroupsModelPlugin_createGroup(groupsPlug); - - Group_setKindAsString(newGroup, "partonomy"); - Group_setName(newGroup, CHAR(STRING_ELT(Rf_getAttrib(subSysGroups, R_NamesSymbol), i))); - SBase_setSBOTerm((SBase_t *) newGroup, 0000633); - - for(int j=0; j < Rf_length(VECTOR_ELT(subSysGroups, i)); j++){ - Member_t* newMember = Member_create(SBMLlevel, SBMLversion, SBMLgroupsversion); - Member_setIdRef(newMember, CHAR(STRING_ELT(VECTOR_ELT(subSysGroups, i), j))); - Group_addMember(newGroup, newMember); - } - //GroupsModelPlugin_addGroup(groupsPlug, newGroup); - } - } - } - - // write SBML file - int result = writeSBML(sbmlDoc, fname); - SEXP out = R_NilValue; - if (result)out = Rf_ScalarLogical(1); - else out = Rf_ScalarLogical(0); - - return out; -} - - - - -/* -------------------------------------------------------------------------- */ +/* sybilSBML.c + Link to libSBML for sybil. + + Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, +Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. +All right reserved. +Email: geliudie@uni-duesseldorf.de + +This file is part of sybilSBML. + +SybilSBML is free software: you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation, either version 3 of the License, or +(at your option) any later version. + +SybilSBML is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. +*/ +#include "config.h" + +#include "sybilSBML.h" + +//new includes @Ardalan Habil +#include <stdlib.h> +#include <string.h> +#include <sbml/xml/XMLTriple.h> +#include <sbml/annotation/CVTerm.h> +#include <sbml/annotation/RDFAnnotationParser.h> +#include <sbml/annotation/ModelHistory.h> +#include <sbml/math/ASTNode.h> +#include <math.h> + +#ifdef HAVE_FBC_PLUGIN +/* FBCv1includes */ + +#include <sbml/extension/SBMLExtensionRegister.h> +#include <sbml/extension/SBMLDocumentPlugin.h> + +#include <sbml/packages/fbc/common/fbcfwd.h> + +/* FBC PLUGINS*/ +#include <sbml/packages/fbc/extension/FbcSBMLDocumentPlugin.h> +#include <sbml/packages/fbc/extension/FbcModelPlugin.h> +#include <sbml/packages/fbc/extension/FbcReactionPlugin.h> +#include <sbml/packages/fbc/extension/FbcSpeciesPlugin.h> + +#include <sbml/packages/fbc/sbml/FluxBound.h> +#include <sbml/packages/fbc/sbml/Objective.h> +#include <sbml/packages/fbc/sbml/FluxObjective.h> +#include <sbml/packages/fbc/sbml/GeneProduct.h> +#include <sbml/packages/fbc/sbml/GeneProductRef.h> +#include <sbml/packages/fbc/sbml/GeneProductAssociation.h> +#include <sbml/packages/fbc/sbml/FbcAssociation.h> +#include <sbml/packages/fbc/sbml/FbcAnd.h> +#include <sbml/packages/fbc/sbml/FbcOr.h> +#endif + +#ifdef HAVE_GROUPS_PLUGIN +/*groups plugin*/ +#include <sbml/packages/groups/common/GroupsExtensionTypes.h> +#include <sbml/packages/groups/extension/GroupsSBMLDocumentPlugin.h> +#include <sbml/packages/groups/extension/GroupsExtension.h> +#include <sbml/packages/groups/extension/GroupsModelPlugin.h> + +#include <sbml/packages/groups/sbml/Group.h> +#include <sbml/packages/groups/sbml/ListOfGroups.h> +#include <sbml/packages/groups/sbml/ListOfMembers.h> +#include <sbml/packages/groups/sbml/Member.h> +#endif + + +static SEXP tagSBMLmodel; +static SEXP tagSBMLdocument; + + +/* -------------------------------------------------------------------------- */ +/* Finalizer */ +/* -------------------------------------------------------------------------- */ + +/* -------------------------------------------------------------------------- */ +/* finalizer for sbml document objects */ +static void sbmlDocumentFinalizer (SEXP sbmldoc) { + if (!R_ExternalPtrAddr(sbmldoc)) { + return; + } + else { + delDocument(sbmldoc); + } +} + + +/* -------------------------------------------------------------------------- */ +/* finalizer for sbml model objects */ +/* +static void sbmlModelFinalizer (SEXP sbmlmodel) { +if (!R_ExternalPtrAddr(sbmlmodel)) { +return; +} +else { +delModel(sbmlmodel); +} +} +*/ + + +/* -------------------------------------------------------------------------- */ +/* help functions */ +/* -------------------------------------------------------------------------- */ + +/* check for pointer to sbml document */ +SEXP isSBMLdocptr(SEXP ptr) { + + SEXP out = R_NilValue; + + if ( (TYPEOF(ptr) == EXTPTRSXP) && + (R_ExternalPtrTag(ptr) == tagSBMLdocument) ) { + out = Rf_ScalarLogical(1); + } + else { + out = Rf_ScalarLogical(0); + } + + return out; +} + +/* check for pointer to sbml model */ +SEXP isSBMLmodptr(SEXP ptr) { + + SEXP out = R_NilValue; + + if ( (TYPEOF(ptr) == EXTPTRSXP) && + (R_ExternalPtrTag(ptr) == tagSBMLmodel) ) { + out = Rf_ScalarLogical(1); + } + else { + out = Rf_ScalarLogical(0); + } + + return out; +} + +/* check for NULL pointer */ +SEXP isNULLptr(SEXP ptr) { + + SEXP out = R_NilValue; + + if ( (TYPEOF(ptr) == EXTPTRSXP) && + (R_ExternalPtrAddr(ptr) == NULL) ) { + out = Rf_ScalarLogical(1); + } + else { + out = Rf_ScalarLogical(0); + } + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* Helper functions */ +/* -------------------------------------------------------------------------- */ + + +// append two string +char * append_strings(const char * old, const char * new, const char* delim) +{ + // find the size of the string to allocate + size_t len = strlen(old) + strlen(new) + strlen(delim) + 1; + + // allocate a pointer to the new string + char *out = malloc(len); + + // concat both strings and return + sprintf(out, "%s%s%s", old, delim , new); + + return out; +} + + + +// Parse Anntatation to modelorg +const char* parseAnnotationTomorg(XMLNode_t* xml) +{ + const XMLNode_t* rdf =NULL; + const XMLNode_t* desc = NULL; + rdf = XMLNode_getChildForName(xml,"RDF"); + if(rdf !=NULL) desc= XMLNode_getChildForName(rdf,"Description"); + const char* annoString = ""; + int firstelement=1; + if (desc!=NULL) + { + + int num=0; + for(num=0;num<XMLNode_getNumChildren(desc);num++) + { + const char* pref= XMLNode_getPrefix(XMLNode_getChild(desc,num)); + + if( strcmp(pref,"bqbiol")==0 || strcmp(pref,"bqmodel")==0 ) + { + CVTerm_t* cv= CVTerm_createFromNode(XMLNode_getChild(desc,num)); + if( CVTerm_getNumResources(cv)>0 ) + { + int numR=0; + if(strcmp(pref,"bqbiol")==0) + { + const char* bioQual = append_strings("bqbiol",BiolQualifierType_toString( CVTerm_getBiologicalQualifierType(cv)),"_"); + if(firstelement==0) annoString = append_strings(annoString,bioQual,";"); + else + { + annoString = append_strings(annoString,bioQual,""); + firstelement=0; + } + + } + if(strcmp(pref,"bqmodel")==0) + { + const char* modQual = append_strings("bqmodel",ModelQualifierType_toString( CVTerm_getModelQualifierType(cv)),"_"); + if(firstelement==0)annoString = append_strings(annoString,modQual,";"); + + else + { + annoString = append_strings(annoString,modQual,""); + firstelement=0; + } + } + + for(numR=0;numR<CVTerm_getNumResources(cv);numR++) + { + // sprintf(annoString+strlen(annoString),"__%s", CVTerm_getResourceURI(cv,numR)); + annoString = append_strings(annoString,CVTerm_getResourceURI(cv,numR),";"); + } + + } + } + + + } + return annoString; + } + else + { + return ""; + } + + + return ""; +} + + + +/* -------------------------------------------------------------------------- */ +/* API-Functions */ +/* -------------------------------------------------------------------------- */ + +/* -------------------------------------------------------------------------- */ +/* initialize sybilSBML */ +SEXP initSBML(void) { + tagSBMLmodel = Rf_install("TYPE_SBML_MODEL"); + tagSBMLdocument = Rf_install("TYPE_SBML_DOCUMENT"); + return R_NilValue; +} + + +/* -------------------------------------------------------------------------- */ +/* get libsbml version number (dotted version) */ +SEXP getLibSBMLversion() { + + SEXP out = R_NilValue; + + const char *vstr = getLibSBMLDottedVersion(); + + out = Rf_mkString(vstr); + + return out; + +} + + +/* -------------------------------------------------------------------------- */ +/* remove sbml document pointer */ +SEXP delDocument(SEXP sbmldoc) { + + SEXP out = R_NilValue; + SBMLDocument_t *del = NULL; + + checkDocument(sbmldoc); + + del = R_ExternalPtrAddr(sbmldoc); + + SBMLDocument_free(del); + R_ClearExternalPtr(sbmldoc); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* remove model pointer */ +SEXP delModel(SEXP sbmlmodel) { + + SEXP out = R_NilValue; + /* Model_t *del = NULL; */ + + checkModel(sbmlmodel); + + /* del = R_ExternalPtrAddr(sbmlmodel); */ + + /* Model_free(del); */ + R_ClearExternalPtr(sbmlmodel); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* read SBML file */ +SEXP readSBMLfile(SEXP fname, SEXP ptrtype) { + + SEXP sfext = R_NilValue; + SEXP ptr, class, file; + const char *rfname = CHAR(STRING_ELT(fname, 0)); + + SBMLDocument_t *sbmldoc; + + /* create sbml document pointer */ + PROTECT(ptr = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(ptr, 0, STRING_ELT(ptrtype, 0)); + + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("sbml_doc_ptr")); + + PROTECT(file = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(file, 0, Rf_mkChar("file_name")); + + /* read the model xml file */ + sbmldoc = readSBML(rfname); + + sfext = R_MakeExternalPtr(sbmldoc, tagSBMLdocument, R_NilValue); + PROTECT(sfext); + R_RegisterCFinalizerEx(sfext, sbmlDocumentFinalizer, TRUE); + Rf_setAttrib(ptr, class, sfext); + Rf_setAttrib(ptr, file, fname); + Rf_classgets(ptr, class); + + UNPROTECT(4); + + return ptr; +} + + +/* -------------------------------------------------------------------------- */ +/* get sbml document level */ +SEXP getSBMLlevel(SEXP sbmldoc) { + + SEXP out = R_NilValue; + unsigned int level; + + checkDocument(sbmldoc); + + level = SBMLDocument_getLevel(R_ExternalPtrAddr(sbmldoc)); + + out = Rf_ScalarInteger(level); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get sbml document version */ +SEXP getSBMLversion(SEXP sbmldoc) { + + SEXP out = R_NilValue; + unsigned int version; + + checkDocument(sbmldoc); + + version = SBMLDocument_getVersion(R_ExternalPtrAddr(sbmldoc)); + + out = Rf_ScalarInteger(version); + + return out; +} + + +/* -------------------------------------------------------------------------- */ + +/* get sbml document FBC version */ +SEXP getSBMLFbcversion(SEXP sbmldoc) { + SEXP out = R_NilValue; + +#ifdef HAVE_FBC_PLUGIN + unsigned int version; + + checkDocument(sbmldoc); + //hierher + SBasePlugin_t * modelPlug= NULL; + modelPlug = SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmldoc)), "fbc"); + if( modelPlug != NULL) + { + if(strcmp("fbc",SBasePlugin_getPackageName(modelPlug) ) ==0) + version = SBasePlugin_getPackageVersion(modelPlug); + else version=0; + } else version=0; + + out = Rf_ScalarInteger(version); +#else + out = Rf_ScalarInteger(0); +#endif + return out; +} + + +/* -------------------------------------------------------------------------- */ + + +/* validate SBML document */ +SEXP validateDocument(SEXP sbmldoc) { + + /* + this is adopted from Michael Lawrence: rsbml + Michael Lawrence (). rsbml: R support for SBML, using libsbml. + R package version 2.18.0. http://www.sbml.org + http://www.bioconductor.org/packages/release/bioc/html/rsbml.html + */ + + SEXP out = R_NilValue; + + unsigned int validation; + + checkDocument(sbmldoc); + + /* number or errors logged when reading SBML file */ + validation = SBMLDocument_getNumErrors(R_ExternalPtrAddr(sbmldoc)); + /* number or errors from structural and mathematical tests */ + validation += SBMLDocument_checkConsistency(R_ExternalPtrAddr(sbmldoc)); + + if (validation > 0) { + out = Rf_ScalarLogical(0); + } + else { + out = Rf_ScalarLogical(1); + } + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get SBML errors */ +SEXP getSBMLerrors(SEXP sbmldoc) { + + /* + this is adopted from Michael Lawrence: rsbml + Michael Lawrence (). rsbml: R support for SBML, using libsbml. + R package version 2.18.0. http://www.sbml.org + http://www.bioconductor.org/packages/release/bioc/html/rsbml.html + */ + + SEXP out = R_NilValue; + SEXP listv = R_NilValue; + SEXP info = R_NilValue; + SEXP warn = R_NilValue; + SEXP error = R_NilValue; + SEXP fatal = R_NilValue; + SEXP class = R_NilValue; + SEXP el = R_NilValue; + + XMLError_t *sbml_err; + + unsigned int nprob, i, ind; + int ninfo = 0, nwarn = 0, nerror = 0, nfatal = 0, nunknown = 0; + + checkDocument(sbmldoc); + + nprob = SBMLDocument_getNumErrors(R_ExternalPtrAddr(sbmldoc)); + + /* + Rprintf("Model Errors: %i\n", nprob); + */ + + if (nprob > 0) { + + /* check how many infos, warnings, errors and fatals we have */ + for (i = 0; i < nprob; i++) { + sbml_err = (XMLError_t *) SBMLDocument_getError(R_ExternalPtrAddr(sbmldoc), i); + if (XMLError_isInfo(sbml_err)) { + ninfo++; + } + else if (XMLError_isWarning(sbml_err)) { + nwarn++; + } + else if (XMLError_isError(sbml_err)) { + nerror++; + } + else if (XMLError_isFatal(sbml_err)) { + nfatal++; + } + else { + nunknown++; + } + } + + /* + Rprintf("number of infos: %i, warnings: %i, errors: %i, falals: %i, unknowns: %i\n", + ninfo, nwarn, nerror, nfatal, nunknown); + */ + + /* + out will be a list of four elements: + infos + warnings + errors + fatals + each of them is a list of three elements: + id + line + column + msg + */ + + PROTECT(out = Rf_allocVector(VECSXP, 4)); + + /* allocate space for each error list */ + PROTECT(info = Rf_allocVector(VECSXP, ninfo)); + PROTECT(warn = Rf_allocVector(VECSXP, nwarn)); + PROTECT(error = Rf_allocVector(VECSXP, nerror)); + PROTECT(fatal = Rf_allocVector(VECSXP, nfatal)); + + SET_VECTOR_ELT(out, 0, info); + SET_VECTOR_ELT(out, 1, warn); + SET_VECTOR_ELT(out, 2, error); + SET_VECTOR_ELT(out, 3, fatal); + + PROTECT(listv = Rf_allocVector(STRSXP, 4)); + SET_STRING_ELT(listv, 0, Rf_mkChar("infos")); + SET_STRING_ELT(listv, 1, Rf_mkChar("warnings")); + SET_STRING_ELT(listv, 2, Rf_mkChar("errors")); + SET_STRING_ELT(listv, 3, Rf_mkChar("fatals")); + Rf_setAttrib(out, R_NamesSymbol, listv); + + /* get the error messages */ + ninfo = 0, nwarn = 0, nerror = 0, nfatal = 0, nunknown = 0; + for (i = 0; i < nprob; i++) { + sbml_err = (XMLError_t *) SBMLDocument_getError(R_ExternalPtrAddr(sbmldoc), i); + el = R_NilValue; + ind = 0; + if (XMLError_isInfo(sbml_err)) { + ind = ninfo++; + el = info; + } + else if (XMLError_isWarning(sbml_err)) { + ind = nwarn++; + el = warn; + } + else if (XMLError_isError(sbml_err)) { + ind = nerror++; + el = error; + } + else if (XMLError_isFatal(sbml_err)) { + ind = nfatal++; + el = fatal; + } + else { + nunknown++; + } + SET_VECTOR_ELT(el, ind, generateProblemMsg(sbml_err)); + } + + /* make the list to be an instance of 'sbml_error' */ + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("sbml_error")); + Rf_classgets(out, class); + + UNPROTECT(7); + + } /* end if nprob > 0 */ + else { + out = Rf_ScalarLogical(1); + } + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get sbml model from sbml document */ +SEXP getSBMLmodel(SEXP sbmldoc, SEXP ptrtype) { + + SEXP smext = R_NilValue; + SEXP ptr, class; + + Model_t *sbmlmodel; + + checkDocument(sbmldoc); + + /* create model pointer */ + PROTECT(ptr = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(ptr, 0, STRING_ELT(ptrtype, 0)); + + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("sbml_model_ptr")); + + /* get sbml model */ + sbmlmodel = SBMLDocument_getModel(R_ExternalPtrAddr(sbmldoc)); + + smext = R_MakeExternalPtr(sbmlmodel, tagSBMLmodel, R_NilValue); + PROTECT(smext); + /* R_RegisterCFinalizerEx(smext, sbmlModelFinalizer, TRUE); */ + Rf_setAttrib(ptr, class, smext); + Rf_classgets(ptr, class); + + UNPROTECT(3); + + return ptr; +} + + +/* -------------------------------------------------------------------------- */ +/* get model id */ +SEXP getSBMLmodId(SEXP sbmlmod) { + + SEXP out = R_NilValue; + const char *mid; + + checkModel(sbmlmod); + + if (Model_isSetId(R_ExternalPtrAddr(sbmlmod))) { + mid = Model_getId(R_ExternalPtrAddr(sbmlmod)); + } + else { + mid = "no_id"; + } + + out = Rf_mkString(mid); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get model name */ +SEXP getSBMLmodName(SEXP sbmlmod) { + + SEXP out = R_NilValue; + const char *mnm; + + checkModel(sbmlmod); + + if (Model_isSetName(R_ExternalPtrAddr(sbmlmod))) { + mnm = Model_getName(R_ExternalPtrAddr(sbmlmod)); + } + else { + mnm = ""; + } + + out = Rf_mkString(mnm); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get model notes */ +SEXP getSBMLmodNotes(SEXP sbmlmod) { + + SEXP out = R_NilValue; + const char *mnotes; + + checkModel(sbmlmod); + + if (SBase_isSetNotes((SBase_t *) R_ExternalPtrAddr(sbmlmod))) { + mnotes = SBase_getNotesString((SBase_t *) R_ExternalPtrAddr(sbmlmod)); + } + else { + mnotes = ""; + } + + out = Rf_mkString(mnotes); + + return out; +} + +/* -------------------------------------------------------------------------- */ +/* get model name */ +SEXP getSBMLmodAnnotation(SEXP sbmlmod) { + + SEXP out = R_NilValue; + const char *manno; + + checkModel(sbmlmod); + + if (SBase_isSetAnnotation((SBase_t *) R_ExternalPtrAddr(sbmlmod))) { + XMLNode_t* xml = SBase_getAnnotation((SBase_t *) R_ExternalPtrAddr(sbmlmod)); + manno = parseAnnotationTomorg(xml); + } + else { + manno = ""; + } + + out = Rf_mkString(manno); + + return out; +} + + + +/* -------------------------------------------------------------------------- */ +/* get number of compartments */ +SEXP getSBMLnumCompart(SEXP sbmlmod) { + + SEXP out = R_NilValue; + unsigned int nc; + + checkModel(sbmlmod); + + nc = Model_getNumCompartments(R_ExternalPtrAddr(sbmlmod)); + + out = Rf_ScalarInteger(nc); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get number of species (metabolites) */ +SEXP getSBMLnumSpecies(SEXP sbmlmod) { + + SEXP out = R_NilValue; + unsigned int nsp; + + checkModel(sbmlmod); + + nsp = Model_getNumSpecies(R_ExternalPtrAddr(sbmlmod)); + + out = Rf_ScalarInteger(nsp); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get number of reactions */ +SEXP getSBMLnumReactions(SEXP sbmlmod) { + + SEXP out = R_NilValue; + unsigned int nr; + + checkModel(sbmlmod); + + nr = Model_getNumReactions(R_ExternalPtrAddr(sbmlmod)); + + out = Rf_ScalarInteger(nr); + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get list of unit definitions */ +SEXP getSBMLunitDefinitionsList(SEXP sbmlmod) { + + SEXP out = R_NilValue; + SEXP class = R_NilValue; + SEXP unl = R_NilValue; + SEXP listv = R_NilValue; + SEXP listn = R_NilValue; + + SEXP unitdefid = R_NilValue; + SEXP unitdef = R_NilValue; + + SEXP unitkind = R_NilValue; + SEXP unitscale = R_NilValue; + SEXP unitexp = R_NilValue; + SEXP unitmult = R_NilValue; + + unsigned int nud, nu, i, j; + + /* ListOf_t *udl; */ + UnitDefinition_t *udlel; + Unit_t *uel; + + checkModel(sbmlmod); + + /* udl = Model_getListOfUnitDefinitions(R_ExternalPtrAddr(sbmlmod)); */ + nud = Model_getNumUnitDefinitions(R_ExternalPtrAddr(sbmlmod)); + + if (nud > 0) { + PROTECT(unitdefid = Rf_allocVector(STRSXP, nud)); + PROTECT(unitdef = Rf_allocVector(VECSXP, nud)); + for (i = 0; i < nud; i++) { + /* udlel = (UnitDefinition_t *) ListOf_get(udl, i); */ + udlel = Model_getUnitDefinition(R_ExternalPtrAddr(sbmlmod), i); + + /* id and unit */ + if (UnitDefinition_isSetId(udlel)) { + SET_STRING_ELT(unitdefid, i, Rf_mkChar(UnitDefinition_getId(udlel))); + + nu = UnitDefinition_getNumUnits(udlel); + + PROTECT(unitkind = Rf_allocVector(STRSXP, nu)); + PROTECT(unitscale = Rf_allocVector(INTSXP, nu)); + PROTECT(unitexp = Rf_allocVector(INTSXP, nu)); + PROTECT(unitmult = Rf_allocVector(REALSXP, nu)); + + for (j = 0; j < nu; j++) { + uel = UnitDefinition_getUnit(udlel, j); + + /* kind */ + if (Unit_isSetKind(uel)) { + SET_STRING_ELT(unitkind, j, Rf_mkChar(UnitKind_toString(Unit_getKind(uel)))); + } + else { + SET_STRING_ELT(unitkind, j, Rf_mkChar("no_kind")); + } + + /* scale */ + if (Unit_isSetScale(uel)) { + INTEGER(unitscale)[j] = Unit_getScale(uel); + } + else { + INTEGER(unitscale)[j] = 0; + } + + /* exponent */ + if (Unit_isSetExponent(uel)) { + INTEGER(unitexp)[j] = Unit_getExponent(uel); + } + else { + INTEGER(unitexp)[j] = 1; + } + + /* multiplier */ + if (Unit_isSetMultiplier(uel)) { + REAL(unitmult)[j] = Unit_getMultiplier(uel); + } + else { + REAL(unitmult)[j] = 1; + } + + } + + PROTECT(unl = Rf_allocVector(VECSXP, 4)); + SET_VECTOR_ELT(unl, 0, unitkind); + SET_VECTOR_ELT(unl, 1, unitscale); + SET_VECTOR_ELT(unl, 2, unitexp); + SET_VECTOR_ELT(unl, 3, unitmult); + + PROTECT(listn = Rf_allocVector(STRSXP, 4)); + SET_STRING_ELT(listn, 0, Rf_mkChar("kind")); + SET_STRING_ELT(listn, 1, Rf_mkChar("scale")); + SET_STRING_ELT(listn, 2, Rf_mkChar("exponent")); + SET_STRING_ELT(listn, 3, Rf_mkChar("multiplier")); + Rf_setAttrib(unl, R_NamesSymbol, listn); + + SET_VECTOR_ELT(unitdef, i, unl); + + UNPROTECT(6); + + } + else { + SET_STRING_ELT(unitdefid, i, Rf_mkChar("no_id")); + } + } + + PROTECT(out = Rf_allocVector(VECSXP, 2)); + SET_VECTOR_ELT(out, 0, unitdefid); + SET_VECTOR_ELT(out, 1, unitdef); + + PROTECT(listv = Rf_allocVector(STRSXP, 2)); + SET_STRING_ELT(listv, 0, Rf_mkChar("definition_id")); + SET_STRING_ELT(listv, 1, Rf_mkChar("definition")); + + Rf_setAttrib(out, R_NamesSymbol, listv); + + /* make the list to be an instance of 'unit_definition' */ + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("unit_definition")); + Rf_classgets(out, class); + + UNPROTECT(5); + } + else { + out = R_NilValue; + } + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* get list of compartments */ +SEXP getSBMLCompartList(SEXP sbmlmod) { + + SEXP out = R_NilValue; + SEXP class = R_NilValue; + SEXP listv = R_NilValue; + SEXP compid = R_NilValue; + SEXP compname = R_NilValue; + SEXP compannot = R_NilValue; + SEXP compnotes = R_NilValue; + SEXP compout = R_NilValue; + + unsigned int nc, i; + + /* ListOf_t *cl; */ + Compartment_t *clel; + + checkModel(sbmlmod); + + /* cl = Model_getListOfCompartments(R_ExternalPtrAddr(sbmlmod)); */ + nc = Model_getNumCompartments(R_ExternalPtrAddr(sbmlmod)); + + if (nc > 0) { + PROTECT(compid = Rf_allocVector(STRSXP, nc)); + PROTECT(compname = Rf_allocVector(STRSXP, nc)); + PROTECT(compannot = Rf_allocVector(STRSXP, nc)); + PROTECT(compnotes = Rf_allocVector(STRSXP, nc)); + + // Counter Variables + int annocount=0; + int notescount=0; + + PROTECT(compout = Rf_allocVector(STRSXP, nc)); + + for (i = 0; i < nc; i++) { + clel = Model_getCompartment(R_ExternalPtrAddr(sbmlmod), i); + /* id */ + if (Compartment_isSetId(clel)) { + SET_STRING_ELT(compid, i, Rf_mkChar(Compartment_getId(clel))); + } + else { + SET_STRING_ELT(compid, i, Rf_mkChar("no_id")); + } + /* name */ + if (Compartment_isSetName(clel)) { + SET_STRING_ELT(compname, i, Rf_mkChar(Compartment_getName(clel))); + } + else { + SET_STRING_ELT(compname, i, Rf_mkChar("")); + } + /* outside */ + if (Compartment_isSetOutside(clel)) { + SET_STRING_ELT(compout, i, Rf_mkChar(Compartment_getOutside(clel))); + } + else { + SET_STRING_ELT(compout, i, Rf_mkChar("")); + } + + /* NEW INFORMATIONS*/ + /* notes */ + if (SBase_isSetNotes((SBase_t *) clel)) { + SET_STRING_ELT(compnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) clel))); + notescount=notescount+1; + } + else { + SET_STRING_ELT(compnotes, i, Rf_mkChar("")); + } + + /* annotation */ + if (SBase_isSetAnnotation((SBase_t *) clel)) { + XMLNode_t* xml = SBase_getAnnotation((SBase_t *) clel); + SET_STRING_ELT(compannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); + annocount=annocount+1; + } + else { + SET_STRING_ELT(compannot, i, Rf_mkChar("")); + } + + + } + + // NULL if empty + if (annocount==0) compannot = R_NilValue; + if (notescount==0) compnotes = R_NilValue; + + PROTECT(out = Rf_allocVector(VECSXP, 5)); + SET_VECTOR_ELT(out, 0, compid); + SET_VECTOR_ELT(out, 1, compname); + SET_VECTOR_ELT(out, 2, compout); + SET_VECTOR_ELT(out, 3, compannot); + SET_VECTOR_ELT(out, 4, compnotes); + + + PROTECT(listv = Rf_allocVector(STRSXP, 5)); + SET_STRING_ELT(listv, 0, Rf_mkChar("id")); + SET_STRING_ELT(listv, 1, Rf_mkChar("name")); + SET_STRING_ELT(listv, 2, Rf_mkChar("outside")); + SET_STRING_ELT(listv, 3, Rf_mkChar("annotation")); + SET_STRING_ELT(listv, 4, Rf_mkChar("notes")); + + + + Rf_setAttrib(out, R_NamesSymbol, listv); + + /* make the list to be an instance of 'compartments_list' */ + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("compartments_list")); + Rf_classgets(out, class); + + UNPROTECT(8); + } + else { + out = R_NilValue; + } + + return out; +} + +/* -------------------------------------------------------------------------- */ +/* get list of species (metabolites) */ +SEXP getSBMLSpeciesList(SEXP sbmlmod) { + + SEXP out = R_NilValue; + SEXP class = R_NilValue; + SEXP listv = R_NilValue; + SEXP metid = R_NilValue; + SEXP metname = R_NilValue; + SEXP metcomp = R_NilValue; + SEXP metcharge = R_NilValue; + SEXP metchemic = R_NilValue; + SEXP metbndcnd = R_NilValue; + SEXP metannot = R_NilValue; + SEXP metnotes = R_NilValue; + + unsigned int nsp, i; + + /* ListOf_t *spl; */ + Species_t *splel; + + checkModel(sbmlmod); + + /* spl = Model_getListOfSpecies(R_ExternalPtrAddr(sbmlmod)); */ + nsp = Model_getNumSpecies(R_ExternalPtrAddr(sbmlmod)); + + + if (nsp > 0) { + PROTECT(metid = Rf_allocVector(STRSXP, nsp)); + PROTECT(metname = Rf_allocVector(STRSXP, nsp)); + PROTECT(metcomp = Rf_allocVector(STRSXP, nsp)); + PROTECT(metcharge = Rf_allocVector(INTSXP, nsp)); + PROTECT(metchemic = Rf_allocVector(STRSXP, nsp)); + PROTECT(metbndcnd = Rf_allocVector(LGLSXP, nsp)); + PROTECT(metannot = Rf_allocVector(STRSXP, nsp)); + PROTECT(metnotes = Rf_allocVector(STRSXP, nsp)); + + int chargecount = 0; + int chcount=0; + int notescount=0; + int annotcount=0; + + for (i = 0; i < nsp; i++) { + /* splel = (Species_t *) ListOf_get(spl, i); */ + splel = Model_getSpecies(R_ExternalPtrAddr(sbmlmod), i); + /* id */ + if (Species_isSetId(splel)) { + SET_STRING_ELT(metid, i, Rf_mkChar(Species_getId(splel))); + } + else { + SET_STRING_ELT(metid, i, Rf_mkChar("no_id")); + } + /* name */ + if (Species_isSetName(splel)) { + SET_STRING_ELT(metname, i, Rf_mkChar(Species_getName(splel))); + } + else { + SET_STRING_ELT(metname, i, Rf_mkChar("")); + } + /* compartment */ + if (Species_isSetCompartment(splel)) { + SET_STRING_ELT(metcomp, i, Rf_mkChar(Species_getCompartment(splel))); + } + else { + SET_STRING_ELT(metcomp, i, Rf_mkChar("")); + } + /* charge */ + if (Species_isSetCharge(splel)) { + INTEGER(metcharge)[i] = Species_getCharge(splel); + } + else { + INTEGER(metcharge)[i] = 0; + } + /* boundary condition */ + if (Species_isSetBoundaryCondition(splel)) { + LOGICAL(metbndcnd)[i] = Species_getBoundaryCondition(splel); + } + else { + LOGICAL(metbndcnd)[i] = 0; + } + + + + /* notes */ + if (SBase_isSetNotes((SBase_t *) splel)) { + SET_STRING_ELT(metnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) splel))); + notescount=notescount+1; + + } + else { + SET_STRING_ELT(metnotes, i, Rf_mkChar("")); + } + + /* annotation */ + if (SBase_isSetAnnotation((SBase_t *) splel)) { + //SET_STRING_ELT(metannot, i, Rf_mkChar(SBase_getAnnotationString((SBase_t *) splel))); + XMLNode_t* xml = SBase_getAnnotation((SBase_t *) splel); + annotcount=annotcount+1; + SET_STRING_ELT(metannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); + } + else { + SET_STRING_ELT(metannot, i, Rf_mkChar("")); + } + + +#ifdef HAVE_FBC_PLUGIN + /* FBC PLUGIN @ Ardalan */ + SBasePlugin_t *SpeciesPlug = SBase_getPlugin((SBase_t *)(splel), "fbc"); + + /* get charge and chemical formula from FBC plugin: */ + if (SpeciesPlug != NULL) { + /* FBCcharge */ + if (FbcSpeciesPlugin_isSetCharge(SpeciesPlug)) { + INTEGER(metcharge)[i] = FbcSpeciesPlugin_getCharge(SpeciesPlug); + chargecount = chargecount + 1; + } + + /* FBC chemicalFormula */ + if (FbcSpeciesPlugin_isSetChemicalFormula(SpeciesPlug)) { + SET_STRING_ELT(metchemic, i, Rf_mkChar(FbcSpeciesPlugin_getChemicalFormula(SpeciesPlug))); + chcount=chcount+1; + } + else { + SET_STRING_ELT(metchemic, i, Rf_mkChar("")); + } + } +#endif + } + + // NULL if empty + if (chargecount == 0) metcharge = R_NilValue; + if (chcount==0) metchemic = R_NilValue; + if (notescount==0) metnotes = R_NilValue; + if (annotcount==0) metannot = R_NilValue; + + PROTECT(out = Rf_allocVector(VECSXP, 8)); + SET_VECTOR_ELT(out, 0, metid); + SET_VECTOR_ELT(out, 1, metname); + SET_VECTOR_ELT(out, 2, metcomp); + SET_VECTOR_ELT(out, 3, metcharge); + SET_VECTOR_ELT(out, 4, metchemic); + SET_VECTOR_ELT(out, 5, metbndcnd); + SET_VECTOR_ELT(out, 6, metannot); + SET_VECTOR_ELT(out, 7, metnotes); + + + PROTECT(listv = Rf_allocVector(STRSXP, 8)); + SET_STRING_ELT(listv, 0, Rf_mkChar("id")); + SET_STRING_ELT(listv, 1, Rf_mkChar("name")); + SET_STRING_ELT(listv, 2, Rf_mkChar("compartment")); + SET_STRING_ELT(listv, 3, Rf_mkChar("charge")); + SET_STRING_ELT(listv, 4, Rf_mkChar("chemicalFormula")); + SET_STRING_ELT(listv, 5, Rf_mkChar("boundaryCondition")); + SET_STRING_ELT(listv, 6, Rf_mkChar("annotation")); + SET_STRING_ELT(listv, 7, Rf_mkChar("notes")); + + + Rf_setAttrib(out, R_NamesSymbol, listv); + + /* make the list to be an instance of 'species_list' */ + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("species_list")); + Rf_classgets(out, class); + + UNPROTECT(11); + } + else { + out = R_NilValue; + } + + return out; +} + + +SEXP getSBMLGroupsList(SEXP sbmlmod) { +#ifdef HAVE_GROUPS_PLUGIN + GroupsModelPlugin_t * modelPlug = NULL; + modelPlug = (GroupsModelPlugin_t *) SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmlmod)), "groups"); + + if(modelPlug != NULL){ + int n = GroupsModelPlugin_getNumGroups(modelPlug); + SEXP rgroups = PROTECT(Rf_allocVector(VECSXP, n)); + SEXP groupnames = PROTECT(Rf_allocVector(STRSXP, n)); + for(int i=0; i<n; i++){ + Group_t* group = GroupsModelPlugin_getGroup(modelPlug, i); + if(Group_isSetName(group) == 1){ // skip group if no name is set + SET_STRING_ELT(groupnames, i, Rf_mkChar(Group_getName(group))); + + int m = Group_getNumMembers(group); + SEXP rmembers = PROTECT(Rf_allocVector(STRSXP, m)); + for(int j=0; j < m; j++){ + Member_t * member = Group_getMember(group, j); + char * memref = Member_getIdRef(member); + SET_STRING_ELT(rmembers, j, Rf_mkChar(memref)); + } + SET_VECTOR_ELT(rgroups, i, rmembers); + UNPROTECT(1); + }else{ + SET_VECTOR_ELT(rgroups, i, R_NilValue); + } + } + Rf_namesgets(rgroups, groupnames); + UNPROTECT(2); + return rgroups; + }else{ + return R_NilValue; + } +#endif + return R_NilValue; +} + +/* -------------------------------------------------------------------------- */ +/* get list of reactions */ +SEXP getSBMLReactionsList(SEXP sbmlmod) { + + SEXP out = R_NilValue; + SEXP class = R_NilValue; + SEXP listv = R_NilValue; + SEXP reactid = R_NilValue; + SEXP reactname = R_NilValue; + SEXP reactrev = R_NilValue; + SEXP reactnotes = R_NilValue; + SEXP reactannot = R_NilValue; + SEXP reactreact = R_NilValue; + SEXP reactprod = R_NilValue; + SEXP reactkl = R_NilValue; + + SEXP parml = R_NilValue; + SEXP parmn = R_NilValue; + SEXP parmid = R_NilValue; + SEXP parmval = R_NilValue; + SEXP parmunit = R_NilValue; + + SEXP fbclb = R_NilValue; //lowerbnd + SEXP fbcup = R_NilValue; //upperbnd + SEXP fbcgene = R_NilValue; //fbc gene Rules + SEXP fbcobj = R_NilValue; // fbc objective + + unsigned int nre, i, j, nreactant, nproduct, nparm; + + /* ListOf_t *rel; */ + Reaction_t *relel; + KineticLaw_t *kl; + Parameter_t *parm; + + checkModel(sbmlmod); + + /* rel = Model_getListOfReactions(R_ExternalPtrAddr(sbmlmod)); */ + /* get number of ractions: */ + nre = Model_getNumReactions(R_ExternalPtrAddr(sbmlmod)); + + if (nre > 0) { + PROTECT(reactid = Rf_allocVector(STRSXP, nre)); + PROTECT(reactname = Rf_allocVector(STRSXP, nre)); + PROTECT(reactrev = Rf_allocVector(LGLSXP, nre)); + PROTECT(reactnotes = Rf_allocVector(STRSXP, nre)); + PROTECT(reactannot = Rf_allocVector(STRSXP, nre)); + PROTECT(reactreact = Rf_allocVector(VECSXP, nre)); + PROTECT(reactprod = Rf_allocVector(VECSXP, nre)); + PROTECT(reactkl = Rf_allocVector(VECSXP, nre)); + + PROTECT(fbclb = Rf_allocVector(REALSXP, nre)); + PROTECT(fbcup = Rf_allocVector(REALSXP, nre)); + PROTECT(fbcgene = Rf_allocVector(STRSXP , nre)); + PROTECT(fbcobj = Rf_allocVector(REALSXP, nre)); + + + int lbcount=0; + int upcount=0; + int genecount=0; + int objcount=0; + int annocount=0; + int notescount=0; + + /* Help Var for Fbc Objective*/ + double Objcoeff = 0; + const char* Objreaction = NULL; + char* objActiv = NULL; + int fbcversion = 0; + + + SBasePlugin_t * modelPlug= NULL; + + #ifdef HAVE_FBC_PLUGIN + /* FBC OBJECTIV @Ardalan*/ + Objective_t * objective = NULL; + FluxObjective_t * fluxObjective = NULL; + modelPlug = SBase_getPlugin((SBase_t *)(R_ExternalPtrAddr(sbmlmod)), "fbc"); + + // Read the Objectives when FBCPlugin for the model exists + // (Save only active objective) + if( modelPlug != NULL) + { + + objActiv = FbcModelPlugin_getActiveObjectiveId(modelPlug); + if(strcmp(objActiv,"") !=0) + { + for(int ob = 0; ob < FbcModelPlugin_getNumObjectives(modelPlug); ob++) + { + objective = FbcModelPlugin_getObjective(modelPlug,ob); + //printf("ObjectiveID: %s \n", Objective_getId(objective) ); + if(strcmp(objActiv,Objective_getId(objective))==0) + { // TODO mehrer FLUXOBJECTIVE; MAXimierung Minimirung? + + // int fob=0; + // for(fob; ob<FbcModelPlugin_getNumObjectives(modelPlug);fob++ ) + // { + fluxObjective = Objective_getFluxObjective(objective,0); + Objreaction = FluxObjective_getReaction(fluxObjective) ; + Objcoeff = FluxObjective_getCoefficient(fluxObjective); + + //printf("ReactionObjectiveID: %s \n", Objreaction); + //printf("Coefficient: %f \n", Objcoeff); + // } + } + + } + + } + + + /* is FBC 1 */ + + if(strcmp("fbc",SBasePlugin_getPackageName(modelPlug) ) ==0) + fbcversion = SBasePlugin_getPackageVersion(modelPlug); + } +#endif + + + for (i = 0; i < nre; i++) { + /* relel = (Reaction_t *) ListOf_get(rel, i); */ + relel = Model_getReaction(R_ExternalPtrAddr(sbmlmod), i); + + nreactant = Reaction_getNumReactants(relel); + nproduct = Reaction_getNumProducts(relel); + + /* id */ + if (Reaction_isSetId(relel)) { + SET_STRING_ELT(reactid, i, Rf_mkChar(Reaction_getId(relel))); + } + else { + SET_STRING_ELT(reactid, i, Rf_mkChar("no_id")); + } + /* name */ + if (Reaction_isSetName(relel)) { + SET_STRING_ELT(reactname, i, Rf_mkChar(Reaction_getName(relel))); + } + else { + SET_STRING_ELT(reactname, i, Rf_mkChar("")); + } + /* reversible */ + if (Reaction_isSetReversible(relel)) { + LOGICAL(reactrev)[i] = Reaction_getReversible(relel); + } + else { + LOGICAL(reactrev)[i] = 0; + } + /* notes */ + if (SBase_isSetNotes((SBase_t *) relel)) { + SET_STRING_ELT(reactnotes, i, Rf_mkChar(SBase_getNotesString((SBase_t *) relel))); + notescount=notescount+1; + } + else { + SET_STRING_ELT(reactnotes, i, Rf_mkChar("")); + } + /* annotation */ + if (SBase_isSetAnnotation((SBase_t *) relel)) { + //SET_STRING_ELT(reactannot, i, Rf_mkChar(SBase_getAnnotationString((SBase_t *) relel))); + XMLNode_t* xml = SBase_getAnnotation((SBase_t *) relel); + SET_STRING_ELT(reactannot, i, Rf_mkChar(parseAnnotationTomorg(xml))); + annocount=annocount+1; + } + else { + SET_STRING_ELT(reactannot, i, Rf_mkChar("")); + } + + +#ifdef HAVE_FBC_PLUGIN + /* FBC LEVEL 2 @Ardalan Habil*/ + + /* ReactionPLugin for FBC 2 */ + SBasePlugin_t *reactionPlug = SBase_getPlugin((SBase_t *)(relel), "fbc"); + + if (reactionPlug != NULL) { + /* LOWERFLUXBOUND */ + if (FbcReactionPlugin_isSetLowerFluxBound(reactionPlug)) + { + parm = Model_getParameterById(R_ExternalPtrAddr (sbmlmod) ,FbcReactionPlugin_getLowerFluxBound(reactionPlug)); + //printf("LowerFLUXBOUND: %f \n", Parameter_getValue(parm)); + REAL(fbclb)[i] = Parameter_getValue(parm); + lbcount=lbcount+1; + } + else{ + REAL(fbclb)[i] = 0; + } + + /* UPPERFLUXBOUND*/ + if (FbcReactionPlugin_isSetUpperFluxBound(reactionPlug)) + { + parm = Model_getParameterById(R_ExternalPtrAddr (sbmlmod) ,FbcReactionPlugin_getUpperFluxBound(reactionPlug)); + //printf("UPPERFLUXBOUND: %f \n", Parameter_getValue(parm)); + REAL(fbcup)[i] = Parameter_getValue(parm); + upcount=upcount+1; + } + else{ + REAL(fbcup)[i] = 0; + } + + /*FBC 1 read */ + if (fbcversion==1) + { + /* Storing FBC1Bounds */ + double fbc1lb=0; + double fbc1up=0; + + for(int fluxb = 0; fluxb < FbcModelPlugin_getNumFluxBounds(modelPlug); fluxb++) + { + FluxBound_t * currentFlux = FbcModelPlugin_getFluxBound(modelPlug,fluxb); + + const char * currentFluxType ; + const char * currentFluxReaction; + + if (FluxBound_isSetReaction(currentFlux)) currentFluxReaction = FluxBound_getReaction(currentFlux); + else continue; + + if(strcmp(currentFluxReaction , Reaction_getId(relel) ) !=0) continue; + + + if (FluxBound_isSetOperation(currentFlux)) currentFluxType = FluxBound_getOperation(currentFlux); + else continue; + + + if(strcmp("greaterEqual" , currentFluxType ) ==0) + { + lbcount=lbcount+1; + if (FluxBound_isSetValue(currentFlux)) fbc1lb = FluxBound_getValue(currentFlux); + else continue; + } + + else if(strcmp("lessEqual" , currentFluxType ) ==0) + { + upcount=upcount+1; + if (FluxBound_isSetValue(currentFlux)) fbc1up = FluxBound_getValue(currentFlux); + else continue; + } + + else if(strcmp("equal" , currentFluxType ) ==0) + { + if (FluxBound_isSetValue(currentFlux)) + { + lbcount=lbcount+1; + upcount=upcount+1; + fbc1lb = FluxBound_getValue(currentFlux); + fbc1up = FluxBound_getValue(currentFlux); + } + else continue; + } + + } + + /* FBC 1 save Bounds */ + REAL(fbclb)[i] = fbc1lb; + REAL(fbcup)[i] = fbc1up; + + } + + + /* FBC GENE */ + if( FbcReactionPlugin_isSetGeneProductAssociation(reactionPlug) ) { + GeneProductAssociation_t* gpa = FbcReactionPlugin_getGeneProductAssociation(reactionPlug); + FbcAssociation_t* asso= (FbcAssociation_t*) GeneProductAssociation_getAssociation(gpa); + SET_STRING_ELT(fbcgene, i, Rf_mkChar(FbcAssociation_toInfix(asso))); + //printf("Gene: %s \n", FbcAssociation_toInfix(asso)); + genecount=genecount+1; + } + else { + SET_STRING_ELT(fbcgene, i, Rf_mkChar("")); + } + + /* FBC OBJECTIVES*/ + if (Objreaction != NULL && strcmp(Objreaction , Reaction_getId(relel) )==0) + { + + REAL(fbcobj)[i] = Objcoeff; + objcount=objcount+1; + } + else{ + REAL(fbcobj)[i] = 0; + } + } else { + REAL(fbclb)[i] = 0; + REAL(fbcup)[i] = 0; + SET_STRING_ELT(fbcgene, i, Rf_mkChar("")); + REAL(fbcobj)[i] = 0; + } +#else + REAL(fbclb)[i] = 0; + REAL(fbcup)[i] = 0; + SET_STRING_ELT(fbcgene, i, Rf_mkChar("")); + REAL(fbcobj)[i] = 0; +#endif + + + /* reactants */ + SET_VECTOR_ELT(reactreact, i, getSpeciesReference(relel, nreactant, 0)); + + /* products */ + SET_VECTOR_ELT(reactprod, i, getSpeciesReference(relel, nproduct, 1)); + + /* kineticLaw */ + if (Reaction_isSetKineticLaw(relel)) { + kl = Reaction_getKineticLaw(relel); + nparm = KineticLaw_getNumParameters(kl); + + if (nparm > 0) { + PROTECT(parmid = Rf_allocVector(STRSXP, nparm)); + PROTECT(parmval = Rf_allocVector(REALSXP, nparm)); + PROTECT(parmunit = Rf_allocVector(STRSXP, nparm)); + + for (j = 0; j < nparm; j++) { + parm = KineticLaw_getParameter(kl, j); + + /* id */ + if (Parameter_isSetId(parm)) { + SET_STRING_ELT(parmid, j, Rf_mkChar(Parameter_getId(parm))); + } + else { + SET_STRING_ELT(parmid, j, Rf_mkChar("no_id")); + } + /* value */ + if (Parameter_isSetValue(parm)) { + REAL(parmval)[j] = Parameter_getValue(parm); + } + else { + REAL(parmval)[j] = 0; + } + /* units */ + if (Parameter_isSetUnits(parm)) { + SET_STRING_ELT(parmunit, j, Rf_mkChar(Parameter_getUnits(parm))); + } + else { + SET_STRING_ELT(parmunit, j, Rf_mkChar("")); + } + } + + PROTECT(parml = Rf_allocVector(VECSXP, 3)); + SET_VECTOR_ELT(parml, 0, parmid); + SET_VECTOR_ELT(parml, 1, parmval); + SET_VECTOR_ELT(parml, 2, parmunit); + + PROTECT(parmn = Rf_allocVector(STRSXP, 3)); + SET_STRING_ELT(parmn, 0, Rf_mkChar("id")); + SET_STRING_ELT(parmn, 1, Rf_mkChar("value")); + SET_STRING_ELT(parmn, 2, Rf_mkChar("units")); + Rf_setAttrib(parml, R_NamesSymbol, parmn); + + UNPROTECT(5); + } + else { + parml = R_NilValue; + } + SET_VECTOR_ELT(reactkl, i, parml); + } + else { + SET_VECTOR_ELT(reactkl, i, R_NilValue); + } + + + } + + // NULL if empty + if(lbcount==0) fbclb = R_NilValue; + if(upcount==0) fbcup = R_NilValue; + if(genecount==0) fbcgene = R_NilValue; + if(objcount==0) fbcobj = R_NilValue; + if(annocount==0) reactannot= R_NilValue; + if(notescount==0) reactnotes= R_NilValue; + + + PROTECT(out = Rf_allocVector(VECSXP, 12)); + SET_VECTOR_ELT(out, 0, reactid); + SET_VECTOR_ELT(out, 1, reactname); + SET_VECTOR_ELT(out, 2, reactrev); + SET_VECTOR_ELT(out, 3, reactnotes); + SET_VECTOR_ELT(out, 4, reactannot); + SET_VECTOR_ELT(out, 5, reactreact); + SET_VECTOR_ELT(out, 6, reactprod); + SET_VECTOR_ELT(out, 7, reactkl); + SET_VECTOR_ELT(out, 8, fbclb); + SET_VECTOR_ELT(out, 9, fbcup); + SET_VECTOR_ELT(out, 10, fbcgene); + SET_VECTOR_ELT(out, 11, fbcobj); + + + PROTECT(listv = Rf_allocVector(STRSXP, 12)); + SET_STRING_ELT(listv, 0, Rf_mkChar("id")); + SET_STRING_ELT(listv, 1, Rf_mkChar("name")); + SET_STRING_ELT(listv, 2, Rf_mkChar("reversible")); + SET_STRING_ELT(listv, 3, Rf_mkChar("notes")); + SET_STRING_ELT(listv, 4, Rf_mkChar("annotation")); + SET_STRING_ELT(listv, 5, Rf_mkChar("reactants")); + SET_STRING_ELT(listv, 6, Rf_mkChar("products")); + SET_STRING_ELT(listv, 7, Rf_mkChar("kinetic_law")); + SET_STRING_ELT(listv, 8, Rf_mkChar("fbc_lowbnd")); + SET_STRING_ELT(listv, 9, Rf_mkChar("fbc_uppbnd")); + SET_STRING_ELT(listv, 10, Rf_mkChar("fbc_gprRules")); + SET_STRING_ELT(listv, 11, Rf_mkChar("fbc_Objectives")); + + Rf_setAttrib(out, R_NamesSymbol, listv); + + /* make the list to be an instance of 'reactions_list' */ + PROTECT(class = Rf_allocVector(STRSXP, 1)); + SET_STRING_ELT(class, 0, Rf_mkChar("reactions_list")); + Rf_classgets(out, class); + + UNPROTECT(15); + } + else { + out = R_NilValue; + } + + return out; +} + +/* -------------------------------------------------------------------------- */ +/* export SBML*/ + +void ParseModtoAnno (SBase_t* comp , char* Mannocopy) + +{ + + char delimiter[] = ";"; + char *ptr; + ptr = strtok(Mannocopy, delimiter); + char* quali; + CVTerm_t *cv; + int first=0; + + while(ptr != NULL) { + + if(strncmp("bqbiol", ptr, strlen("bqbiol")) == 0) + { + if (first != 0){ SBase_addCVTerm((SBase_t*)comp, cv);CVTerm_free(cv);} + //CVTerm_free(cv); + quali = strcpy(&ptr[0],&ptr[7]); + cv = CVTerm_createWithQualifierType(BIOLOGICAL_QUALIFIER); + CVTerm_setBiologicalQualifierTypeByString( cv, (const char*) quali); + first=1; + } + else if(strncmp("bqmodel", ptr, strlen("bqmodel")) == 0) + { + if (first != 0) { SBase_addCVTerm((SBase_t*)comp, cv);CVTerm_free(cv);} + //CVTerm_free(cv); + quali = strcpy(&ptr[0],&ptr[8]); + cv = CVTerm_createWithQualifierType(MODEL_QUALIFIER); + CVTerm_setModelQualifierTypeByString( cv, (const char*) quali); + } + else + { + CVTerm_addResource(cv,ptr ); + } + + // naechsten Abschnitt erstellen + ptr = strtok(NULL, delimiter); + } + SBase_addCVTerm((SBase_t*)comp, cv); + +} + + + +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 subSysGroups, 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) +{ +#if defined(HAVE_FBC_PLUGIN) && defined(HAVE_GROUPS_PLUGIN) + //Varaibles from R + const char* fname = CHAR(STRING_ELT(filename, 0)); + const char* model_desc = CHAR(STRING_ELT(mod_desc, 0)); + const char* model_name = CHAR(STRING_ELT(mod_name, 0)); + + int SBMLlevel = INTEGER(level)[0]; + int SBMLversion = INTEGER(version)[0]; + int SBMLfbcversion = INTEGER(FbcLevel)[0]; + int SBMLgroupsversion = 1; + double sybilmax = REAL(sybil_max)[0]; + double sybilmin = sybilmax*(-1); + + // variable FBC + XMLNamespaces_t * fbc; + SBMLNamespaces_t * sbmlns; + FluxBound_t * fluxBound; + Objective_t * objective; + FluxObjective_t * fluxObjective; + SBMLDocumentPlugin_t * docPlug; + SBasePlugin_t * modelPlug; + SBasePlugin_t *reactionPlug; + SBasePlugin_t *SpeciesPlug ; + + FbcAssociation_t* asso; + + + // Variable inital + + SBMLDocument_t* sbmlDoc; + Model_t* model; + XMLNamespaces_t* xmlns; + + UnitDefinition_t* unitdef; + Unit_t* unit; + + Species_t *sp; + Reaction_t* reaction; + SpeciesReference_t* spr; + Compartment_t* comp; + KineticLaw_t* kl; + Parameter_t* para; + + // ASTNode_t* flux; + ASTNode_t* astMath; + //ASTNode_t* ast; + //char* mathXMLString; + + /*--------------------------------------------------------------------------- + * + * Creates an SBMLDocument object + * + *---------------------------------------------------------------------------*/ + + if (SBMLlevel == 1 || SBMLlevel == 2) + { + sbmlDoc = SBMLDocument_createWithLevelAndVersion(SBMLlevel,SBMLversion); + xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); + XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); + } + else if(SBMLlevel == 3) + { + if(SBMLfbcversion == 0) + { + sbmlDoc = SBMLDocument_createWithLevelAndVersion(3,1); + xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); + XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); + + } else { + + /* FBC LEVEL */ + /* get fbc registry entry */ + SBMLExtension_t *sbmlext = SBMLExtensionRegistry_getExtension("fbc"); + + /* create the sbml namespaces object with fbc */ + XMLNamespaces_t * fbc = XMLNamespaces_create(); + XMLNamespaces_add(fbc, SBMLExtension_getURI(sbmlext, 3, 1, SBMLfbcversion), "fbc"); + + sbmlns = SBMLNamespaces_create(3, 1); + SBMLNamespaces_addNamespaces(sbmlns, fbc); + + /* add groups extention */ + SBMLExtension_t *sbmlgext = SBMLExtensionRegistry_getExtension("groups"); + XMLNamespaces_t * groups = XMLNamespaces_create(); + XMLNamespaces_add(groups, SBMLExtension_getURI(sbmlgext, SBMLlevel, SBMLversion, SBMLgroupsversion), "groups"); + SBMLNamespaces_addNamespaces(sbmlns, groups); + + /* create the document */ + sbmlDoc = SBMLDocument_createWithSBMLNamespaces(sbmlns); + + /* XHTML for notes*/ + xmlns = (XMLNamespaces_t*) SBMLDocument_getNamespaces(sbmlDoc); + XMLNamespaces_add(xmlns, "http://www.w3.org/1999/xhtml", "html"); + + /* set the fbc reqd attribute to false */ + docPlug = (SBMLDocumentPlugin_t*)(SBase_getPlugin((SBase_t*)(sbmlDoc), "fbc")); + SBMLDocumentPlugin_setRequired(docPlug, 0); + + } + + } + + + /*--------------------------------------------------------------------------- + * + * Creates a Model object inside the SBMLDocument object. + * + *---------------------------------------------------------------------------*/ + + model = SBMLDocument_createModel(sbmlDoc); + Model_setId(model,model_name); + + // Get a SBasePlugin_t object plugged in the model object. + if(SBMLfbcversion == 2) + { + modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); + + // set the fbc strict attribute + FbcModelPlugin_setStrict(modelPlug, 1); + } + + // Model NOTERS + if (!Rf_isNull(mod_notes)) + { + char *Modnotes = (char*) CHAR(STRING_ELT(mod_notes, 0)); + if ((Modnotes != NULL) && (Modnotes[0] != '\0')) + { + //printf("Canno: %s", Cnotes); + SBase_setNotesString((SBase_t*) model , Modnotes); + } + } + + /*Annotation*/ + if (!Rf_isNull(mod_anno) ) + { char *Manno = (char*) CHAR(STRING_ELT(mod_anno, 0)); + if((Manno != NULL) && (Manno[0] != '\0' )) + { + SBase_setMetaId((SBase_t*)model,model_name); + char Mannocopy[strlen(Manno)+1]; + strcpy(Mannocopy,Manno); + // PARSING + ParseModtoAnno((SBase_t*)model, Mannocopy); + + } + } + + /*--------------------------------------------------------------------------- + * + * Creates UnitDefinition objects inside the Model object. + * + *---------------------------------------------------------------------------*/ + /* + unitdef = Model_createUnitDefinition(model); + UnitDefinition_setId(unitdef,"litre_per_mole_per_second"); + + // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") + + unit = UnitDefinition_createUnit(unitdef); + Unit_setKind(unit,UNIT_KIND_MOLE); + Unit_setExponent(unit,-1); + + // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") + + unit = UnitDefinition_createUnit(unitdef); + Unit_setKind(unit,UNIT_KIND_LITRE); + Unit_setExponent(unit,1); + + // Creates an Unit inside the UnitDefinition object ("litre_per_mole_per_second") + + unit = UnitDefinition_createUnit(unitdef); + Unit_setKind(unit,UNIT_KIND_SECOND); + Unit_setExponent(unit,-1); + + */ + + /*--------------------------------------------------------------------------- + * + * Creates a Compartment object inside the Model object. + * + *---------------------------------------------------------------------------*/ + + const char *sName; + int i; + int hasBoundary=0; + for (i=0; i<LENGTH(mod_compart); i++) + { + sName = CHAR(STRING_ELT(mod_compart, i)); + comp = Model_createCompartment(model); + Compartment_setId(comp,sName); + Compartment_setConstant(comp,1); + if( strcmp(sName,"BOUNDARY")==0 || strcmp(sName,"Boundary")==0 || strcmp(sName,"boundary")==0)hasBoundary=1; + if (!Rf_isNull(com_notes) && Rf_length(com_notes) > 1) + { + char *Cnotes = (char*) CHAR(STRING_ELT(com_notes, i)); + if ((Cnotes != NULL) && (Cnotes[0] != '\0')) + { + //printf("Canno: %s", Cnotes); + SBase_setNotesString((SBase_t*)comp, Cnotes); + } + } + + + if (!Rf_isNull(com_anno) && Rf_length(com_anno) > 1 ) + { char *Manno = (char*) CHAR(STRING_ELT(com_anno, i)); + if((Manno != NULL) && (Manno[0] != '\0' )) + { + SBase_setMetaId((SBase_t*)comp, CHAR(STRING_ELT(mod_compart, i))); + char Mannocopy[strlen(Manno)+1]; + strcpy(Mannocopy,Manno); + ParseModtoAnno((SBase_t*) comp,Mannocopy); + + } + } + + } + + + /* Boundary Compartment */ + if(hasBoundary==0 && Rf_isNull(met_bnd) && Rf_length(met_bnd) <= 1 && !Rf_isNull(ex_react)) + { + comp = Model_createCompartment(model); + Compartment_setId(comp,"BOUNDARY"); + Compartment_setConstant(comp,1); + hasBoundary=1; + } + /*--------------------------------------------------------------------------- + * + * Creates Species objects inside the Model object. + * + *---------------------------------------------------------------------------*/ + for (i=0; i<LENGTH(met_name); i++) + { + + + sp = Model_createSpecies(model); + Species_setId(sp,CHAR(STRING_ELT(met_id, i))); + Species_setName(sp,CHAR(STRING_ELT(met_name, i))); + Species_setCompartment(sp,CHAR(STRING_ELT(met_comp, i))); + Species_setHasOnlySubstanceUnits(sp, 0); + Species_setConstant(sp, 0); + + //Bondary Condition + if (!Rf_isNull(met_bnd) && Rf_length(met_bnd) > 1) Species_setBoundaryCondition(sp, LOGICAL(met_bnd)[i]); + else Species_setBoundaryCondition(sp, 0); + + + int hasNotes=0; + const char* metnote=""; + if (!Rf_isNull(met_form) && Rf_length(met_form) > 1) + { + if (SBMLfbcversion >0) + { + SpeciesPlug = SBase_getPlugin((SBase_t *)(sp), "fbc"); + FbcSpeciesPlugin_setChemicalFormula(SpeciesPlug, CHAR(STRING_ELT(met_form, i))); + } + + else{ + metnote = append_strings(metnote,"<html:p>FORMULA: ",""); + metnote =append_strings(metnote,CHAR(STRING_ELT(met_form, i)),""); + metnote =append_strings(metnote," </html:p>",""); + hasNotes=1; + } + } + + if (!Rf_isNull(met_charge) && Rf_length(met_charge) > 1) + { + if (SBMLfbcversion >0) + { + SpeciesPlug = SBase_getPlugin((SBase_t *)(sp), "fbc"); + FbcSpeciesPlugin_setCharge(SpeciesPlug, INTEGER(met_charge)[i]); + } + else + { + metnote = append_strings(metnote,"<html:p>CHARGE: ",""); + char chint[256]; + sprintf(chint, "%d", INTEGER(met_charge)[i]); + metnote =append_strings(metnote,chint,""); + metnote =append_strings(metnote," </html:p>",""); + hasNotes=1; + } + } + + + if (!Rf_isNull(met_notes) && Rf_length(met_notes) > 1) + { + char *Mnotes = (char*) CHAR(STRING_ELT(met_notes, i)); + if ((Mnotes != NULL) && (Mnotes[0] != '\0')) + { + SBase_setNotesString((SBase_t*)sp, Mnotes); + hasNotes=0; + } + + } + + + if(hasNotes !=0 )SBase_setNotesString((SBase_t*)sp, metnote); + + if (!Rf_isNull(met_anno) && Rf_length(met_anno) > 1 ) + { char *Manno = (char*) CHAR(STRING_ELT(met_anno, i)); + + if((Manno != NULL) && (Manno[0] != '\0' )) + { + + SBase_setMetaId((SBase_t*)sp, CHAR(STRING_ELT(met_id, i))); + + // COPY STRING + char *Manno = (char*) CHAR(STRING_ELT(met_anno, i)); + char Mannocopy[strlen(Manno)+1]; + strcpy(Mannocopy,Manno); + // PARSING + ParseModtoAnno((SBase_t*)sp, Mannocopy); + + } + } + + + + } + /*--------------------------------------------------------------------------- + * + * Creates Reaction objects inside the Model object. + * + *---------------------------------------------------------------------------*/ + + /* LISTOFGENES + * + */ + if(SBMLfbcversion == 2 && Rf_length(gpr) > 1) + { + if (!Rf_isNull(gpr) && Rf_length(gpr) > 1) + { + modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); + //GeneProduct_t* gene; + char* genid = malloc( 100 ); + + for (i=0; i<LENGTH(allgenes); i++) + { + GeneProduct_t* gene = GeneProduct_create(3,1,2); + sprintf(genid,"G_%s", CHAR(STRING_ELT(allgenes, i))); + GeneProduct_setId(gene ,genid); + GeneProduct_setLabel(gene ,CHAR(STRING_ELT(allgenes, i))); + FbcModelPlugin_addGeneProduct(modelPlug,gene); + } + free(genid); + } + /* + ListOfParemters + */ + + // create the Parameters + + para = Model_createParameter(model); + Parameter_setId(para, "default_lb"); + Parameter_setConstant(para, 1); + Parameter_setValue(para, sybilmin); + SBase_setSBOTerm((SBase_t *)para,626); + + para = Model_createParameter(model); + Parameter_setId(para, "default_ub"); + Parameter_setConstant(para, 1); + Parameter_setValue(para, sybilmax); + SBase_setSBOTerm((SBase_t *)para,626); + + para = Model_createParameter(model); + Parameter_setId(para, "default_0"); + Parameter_setConstant(para, 1); + Parameter_setValue(para, 0); + SBase_setSBOTerm((SBase_t *)para,626); + + } + + + // LOOP FOR REACTION + for (i=0; i<LENGTH(react_name); i++) + { + reaction = Model_createReaction(model); + + Reaction_setId(reaction, CHAR(STRING_ELT(react_id, i))); + Reaction_setName(reaction, CHAR(STRING_ELT(react_name, i))); + Reaction_setReversible(reaction,LOGICAL(react_rev)[i]); + Reaction_setFast(reaction, 0); + + if(SBMLfbcversion == 2) + { + // FBCv2 + reactionPlug = SBase_getPlugin((SBase_t *)(reaction), "fbc"); + GeneProductAssociation_t* gpa = GeneProductAssociation_create(3,1,2); + + // FbcAnd_t * und= FbcAnd_create(3,1,2); + asso= FbcAssociation_parseFbcInfixAssociation(CHAR(STRING_ELT(gpr, i)),modelPlug); + GeneProductAssociation_setAssociation(gpa,asso); + FbcReactionPlugin_setGeneProductAssociation(reactionPlug,gpa); + } + + + + const char* notesString = ""; + + + + if (!Rf_isNull(react_notes) && Rf_length(react_notes) > 1) + { + char *Rnotes = (char*) CHAR(STRING_ELT(react_notes, i)); + if ((Rnotes != NULL) && (Rnotes[0] != '\0')) + { + //printf("Reaction Nores:%s ",Rnotes); + SBase_setNotesString((SBase_t*)reaction, Rnotes); + } + + } + else + { + if(SBMLfbcversion == 0) + { + if (!Rf_isNull(gpr) && Rf_length(gpr) > 1) + { + notesString = append_strings(notesString,"<html:p>GENE_ASSOCIATION: ",""); + notesString =append_strings(notesString,CHAR(STRING_ELT(gpr, i)),""); + notesString =append_strings(notesString," </html:p>",""); + } + if (!Rf_isNull(subSys) && Rf_length(subSys) > 1) + { + notesString = append_strings(notesString,"<html:p>SUBSYSTEM: ",""); + notesString =append_strings(notesString,CHAR(STRING_ELT(subSys, i)),""); + notesString =append_strings(notesString," </html:p>",""); + } + + SBase_setNotesString((SBase_t*)reaction, notesString); + } + } + + const double *lower_bnd = REAL(lowbnd); + const double *upper_bnd = REAL(uppbnd); + + // KineticLaw + if(SBMLfbcversion == 0) + { + kl = Reaction_createKineticLaw(reaction); + + astMath = ASTNode_createWithType(AST_NAME); + ASTNode_setName(astMath, "FLUX_VALUE"); + + KineticLaw_setMath( kl, astMath); + + + para = KineticLaw_createParameter( kl ); + Parameter_setId(para, "LOWER_BOUND"); + Parameter_setValue( para, lower_bnd[i]); + //Parameter_setUnits( para, "litre_per_mole_per_second"); + + para = KineticLaw_createParameter( kl ); + Parameter_setId(para, "UPPER_BOUND"); + Parameter_setValue( para, upper_bnd[i]); + //Parameter_setUnits( para, "litre_per_mole_per_second"); + + para = KineticLaw_createParameter( kl ); + Parameter_setId(para, "OBJECTIVE_COEFFICIENT"); + Parameter_setValue( para, INTEGER(obj_coef)[i]); + + para = KineticLaw_createParameter( kl ); + Parameter_setId(para, "FLUX_VALUE"); + Parameter_setValue( para, 0); + } + + + int isexchange=0; + int k; + if (Rf_isNull(met_bnd) && Rf_length(met_bnd) <= 1 && !Rf_isNull(ex_react)) + for (k=0; k<LENGTH(ex_react); k++) + if( i+1 == INTEGER(ex_react)[k]) + isexchange=1; + + int j=0; + for (j=0; j<LENGTH(met_id); j++) + { + + int hash = LENGTH(met_id) * i + j; + if (REAL(SMatrix)[hash] != 0.00 ) + { + + if(REAL(SMatrix)[hash] < 0.00) + { + spr = Reaction_createReactant(reaction); + SpeciesReference_setConstant(spr, 1); + SpeciesReference_setSpecies(spr,CHAR(STRING_ELT(met_id, j))); + SpeciesReference_setStoichiometry(spr, fabs(REAL(SMatrix)[hash])); + + //is Exchange Reaction + if(isexchange==1 && !Rf_isNull(ex_react)) + { + /* Create boundary Species */ + sp = Model_createSpecies(model); + + Species_setId(sp, append_strings(CHAR(STRING_ELT(met_id, j)),"BOUNDARY","_") ); + Species_setName(sp,append_strings(CHAR(STRING_ELT(met_name, j)),"BOUNDARY"," ") ); + + Species_setCompartment(sp,"BOUNDARY"); + Species_setHasOnlySubstanceUnits(sp, 0); + Species_setBoundaryCondition(sp, 1); + Species_setConstant(sp, 1); + + /* Add boundary Species as Product */ + spr = Reaction_createProduct(reaction); + SpeciesReference_setSpecies(spr,append_strings(CHAR(STRING_ELT(met_id, j)),"BOUNDARY","_") ); + SpeciesReference_setStoichiometry(spr,1); + + SpeciesReference_setConstant(spr, 1); + } + + + }else{ + spr = Reaction_createProduct(reaction); + SpeciesReference_setConstant(spr, 1); + SpeciesReference_setSpecies(spr,CHAR(STRING_ELT(met_id, j))); + SpeciesReference_setStoichiometry(spr, fabs(REAL(SMatrix)[hash])); + } + + } + } + + + + /*Annotation*/ + if (!Rf_isNull(react_anno) && Rf_length(react_anno) > 1 ) + { char *Manno = (char*) CHAR(STRING_ELT(react_anno, i)); + if((Manno != NULL) && (Manno[0] != '\0' )) + { + SBase_setMetaId((SBase_t*)reaction, CHAR(STRING_ELT(react_id, i))); + char Mannocopy[strlen(Manno)+1]; + strcpy(Mannocopy,Manno); + // PARSING + ParseModtoAnno((SBase_t*)reaction, Mannocopy); + + } + } + + + + /* FBC LEVEL 2 */ + if(SBMLfbcversion == 2) + { + // Get a SBasePlugin_t object plugged in the reaction object. + + reactionPlug = SBase_getPlugin((SBase_t *)(reaction), "fbc"); + + const char* para_lb; + const char* para_ub; + + //default Parameter or new one + if (lower_bnd[i]<= sybilmin) + { + para_lb="default_lb"; + } + else if (lower_bnd[i] == 0) + { + para_lb="default_0"; + } + else + { //creacte Lower_bound Paramater + para = Model_createParameter(model); + Parameter_setId(para, append_strings(CHAR(STRING_ELT(react_id, i)),"lower_bound","_")); + Parameter_setConstant(para, 1); + Parameter_setValue(para, lower_bnd[i]); + SBase_setSBOTerm((SBase_t *)para,625); + + para_lb=append_strings(CHAR(STRING_ELT(react_id, i)),"lower_bound","_"); + + } + + if (upper_bnd[i] >= sybilmax) + { + para_ub="default_ub"; + } + + else if (upper_bnd[i] == 0) + { + para_ub="default_0"; + } + + else + { + //creacte upper_bound Paramater + para = Model_createParameter(model); + Parameter_setId(para, append_strings(CHAR(STRING_ELT(react_id, i)),"upper_bound","_")); + Parameter_setConstant(para, 1); + Parameter_setValue(para, upper_bnd[i]); + SBase_setSBOTerm((SBase_t *)para,625); + + para_ub=append_strings(CHAR(STRING_ELT(react_id, i)),"upper_bound","_"); + } + + // set the flux bounds for this reaction + FbcReactionPlugin_setLowerFluxBound(reactionPlug, para_lb); + FbcReactionPlugin_setUpperFluxBound(reactionPlug, para_ub); + + // OBJECTIVES + if (INTEGER(obj_coef)[i]!=0) + { + objective = Objective_create(3, 1, 2); + Objective_setId(objective, "obj"); + Objective_setType(objective, "maximize"); + + fluxObjective = Objective_createFluxObjective(objective); + FluxObjective_setReaction(fluxObjective, CHAR(STRING_ELT(react_id, i))); + FluxObjective_setCoefficient(fluxObjective, INTEGER(obj_coef)[i]); + + FbcModelPlugin_addObjective(modelPlug, objective); + + // mark obj1 as active objective + FbcModelPlugin_setActiveObjectiveId(modelPlug, "obj"); + + } + } + + + }// ENDE REACTION + if(SBMLfbcversion == 1) + { + + // FBC LEVEL 1 + + // Get a SBasePlugin_t object plugged in the model object. + + modelPlug = SBase_getPlugin((SBase_t *)(model), "fbc"); + int ObjCounter = 0; + for (i=0; i<LENGTH(react_name); i++) + { + + const double *lower_bnd = REAL(lowbnd); + const double *upper_bnd = REAL(uppbnd); + + char buf[21]; // changed from 20 to 21 to avoid buffer overflow + // FBC1 FLUXBOUNDS + sprintf(buf, "LOWER_BOUND%d", i); + if (INTEGER(obj_coef)[i] != 1) + { + fluxBound = FluxBound_create(3, 1, 1); + FluxBound_setId(fluxBound, buf); + FluxBound_setReaction(fluxBound, CHAR(STRING_ELT(react_id, i))); + FluxBound_setOperation(fluxBound, "greaterEqual"); + FluxBound_setValue(fluxBound, lower_bnd[i]); + FbcModelPlugin_addFluxBound(modelPlug, fluxBound); + + //printf("Upper: %s\n", buf); + sprintf(buf, "UPPER_BOUND%d", i); + fluxBound = FluxBound_create(3, 1, 1); + FluxBound_setId(fluxBound, buf); + FluxBound_setReaction(fluxBound, CHAR(STRING_ELT(react_id, i))); + FluxBound_setOperation(fluxBound, "lessEqual"); + FluxBound_setValue(fluxBound, upper_bnd[i]); + + FbcModelPlugin_addFluxBound(modelPlug, fluxBound); + } + + if (INTEGER(obj_coef)[i] == 1 && ObjCounter == 0) + { + sprintf(buf, "OBJ%d", i); + objective = Objective_create(3, 1, 1); + Objective_setId(objective, buf); + Objective_setType(objective, "maximize"); + + fluxObjective = Objective_createFluxObjective(objective); + FluxObjective_setReaction(fluxObjective, CHAR(STRING_ELT(react_id, i))); + FluxObjective_setCoefficient(fluxObjective, 1); + + FbcModelPlugin_addObjective(modelPlug, objective); + FbcModelPlugin_setActiveObjectiveId(modelPlug, buf); + ObjCounter = ObjCounter +1; + } + + + + } + } + + /* add subsystem as groups if fbc is >= 2 */ + if(SBMLfbcversion >= 2){ + if(!Rf_isNull(subSysGroups)){ + GroupsModelPlugin_t* groupsPlug = NULL; + groupsPlug = (GroupsModelPlugin_t*) SBase_getPlugin((SBase_t *)(model), "groups"); + + for(int i=0; i < Rf_length(subSysGroups); i++){ + Group_t* newGroup = GroupsModelPlugin_createGroup(groupsPlug); + + Group_setKindAsString(newGroup, "partonomy"); + Group_setName(newGroup, CHAR(STRING_ELT(Rf_getAttrib(subSysGroups, R_NamesSymbol), i))); + SBase_setSBOTerm((SBase_t *) newGroup, 0000633); + + for(int j=0; j < Rf_length(VECTOR_ELT(subSysGroups, i)); j++){ + Member_t* newMember = Member_create(SBMLlevel, SBMLversion, SBMLgroupsversion); + Member_setIdRef(newMember, CHAR(STRING_ELT(VECTOR_ELT(subSysGroups, i), j))); + Group_addMember(newGroup, newMember); + } + //GroupsModelPlugin_addGroup(groupsPlug, newGroup); + } + } + } + + // write SBML file + int result = writeSBML(sbmlDoc, fname); + SEXP out = R_NilValue; + if (result)out = Rf_ScalarLogical(1); + else out = Rf_ScalarLogical(0); +#else + SEXP out = Rf_ScalarLogical(0);/* no success */ +#endif + + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* check, if FBC-Plugin is available */ +SEXP isAvailableFbcPlugin() { + SEXP out = R_NilValue; +#ifdef HAVE_FBC_PLUGIN + out = Rf_ScalarLogical(1); +#else + out = Rf_ScalarLogical(0); +#endif + return out; +} + + +/* -------------------------------------------------------------------------- */ +/* check, if Groups-Plugin is available */ +SEXP isAvailableGroupsPlugin() { + SEXP out = R_NilValue; +#ifdef HAVE_GROUPS_PLUGIN + out = Rf_ScalarLogical(1); +#else + out = Rf_ScalarLogical(0); +#endif + return out; +} + + +/* -------------------------------------------------------------------------- */ diff --git a/src/sybilSBML.h b/src/sybilSBML.h index 6393177a8b161b24de6c767be6dd20a71008bedd..3f7526a9b3028359fdf7d8338798ff1e592e6044 100644 --- a/src/sybilSBML.h +++ b/src/sybilSBML.h @@ -1,115 +1,121 @@ -/* sybilSBML.h - Link to libSBML for sybil. - - Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, - Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. - All right reserved. - Email: geliudie@uni-duesseldorf.de - - This file is part of sybilSBML. - - SybilSBML is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - SybilSBML is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. -*/ - -#include "sbml.h" - -/* -------------------------------------------------------------------------- */ -/* help functions */ -/* -------------------------------------------------------------------------- */ - -/* check for pointer to sbml document */ -SEXP isSBMLdocptr(SEXP ptr); - -/* check for pointer to sbml model */ -SEXP isSBMLmodptr(SEXP ptr); - -/* check for NULL pointer */ -SEXP isNULLptr(SEXP ptr); - - -/* -------------------------------------------------------------------------- */ -/* API functions */ -/* -------------------------------------------------------------------------- */ - -/* get libsbml version number (dotted version) */ -SEXP getLibSBMLversion(); - -/* initialize sybilSBML */ -SEXP initSBML(void); - -/* remove sbml document pointer */ -SEXP delDocument(SEXP sbmldoc); - -/* remove model pointer */ -SEXP delModel(SEXP sbmlmodel); - -/* read SBML file */ -SEXP readSBMLfile(SEXP fname, SEXP ptrtype); - -/* get sbml document level */ -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); - -/* get SBML errors */ -SEXP getSBMLerrors(SEXP sbmldoc); - -/* get sbml model from sbml document */ -SEXP getSBMLmodel(SEXP sbmldoc, SEXP ptrtype); - -/* get model id */ -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); - -/* get number of species (metabolites) */ -SEXP getSBMLnumSpecies(SEXP sbmlmod); - -/* get number of reactions */ -SEXP getSBMLnumReactions(SEXP sbmlmod); - -/* get list of unit definitions */ -SEXP getSBMLunitDefinitionsList(SEXP sbmlmod); - -/* get list of compartments */ -SEXP getSBMLCompartList(SEXP sbmlmod); - -/* get list of species (metabolites) */ -SEXP getSBMLSpeciesList(SEXP sbmlmod); - -/* get list of groups */ -SEXP getSBMLGroupsList(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 subSysGroups, 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); +/* sybilSBML.h + Link to libSBML for sybil. + + Copyright (C) 2010-2013 Gabriel Gelius-Dietrich, Dpt. for Bioinformatics, + Institute for Informatics, Heinrich-Heine-University, Duesseldorf, Germany. + All right reserved. + Email: geliudie@uni-duesseldorf.de + + This file is part of sybilSBML. + + SybilSBML is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + SybilSBML is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with sybilSBML. If not, see <http://www.gnu.org/licenses/>. +*/ + +#include "sbml.h" + +/* -------------------------------------------------------------------------- */ +/* help functions */ +/* -------------------------------------------------------------------------- */ + +/* check for pointer to sbml document */ +SEXP isSBMLdocptr(SEXP ptr); + +/* check for pointer to sbml model */ +SEXP isSBMLmodptr(SEXP ptr); + +/* check for NULL pointer */ +SEXP isNULLptr(SEXP ptr); + + +/* -------------------------------------------------------------------------- */ +/* API functions */ +/* -------------------------------------------------------------------------- */ + +/* get libsbml version number (dotted version) */ +SEXP getLibSBMLversion(); + +/* initialize sybilSBML */ +SEXP initSBML(void); + +/* remove sbml document pointer */ +SEXP delDocument(SEXP sbmldoc); + +/* remove model pointer */ +SEXP delModel(SEXP sbmlmodel); + +/* read SBML file */ +SEXP readSBMLfile(SEXP fname, SEXP ptrtype); + +/* get sbml document level */ +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); + +/* get SBML errors */ +SEXP getSBMLerrors(SEXP sbmldoc); + +/* get sbml model from sbml document */ +SEXP getSBMLmodel(SEXP sbmldoc, SEXP ptrtype); + +/* get model id */ +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); + +/* get number of species (metabolites) */ +SEXP getSBMLnumSpecies(SEXP sbmlmod); + +/* get number of reactions */ +SEXP getSBMLnumReactions(SEXP sbmlmod); + +/* get list of unit definitions */ +SEXP getSBMLunitDefinitionsList(SEXP sbmlmod); + +/* get list of compartments */ +SEXP getSBMLCompartList(SEXP sbmlmod); + +/* get list of species (metabolites) */ +SEXP getSBMLSpeciesList(SEXP sbmlmod); + +/* get list of groups */ +SEXP getSBMLGroupsList(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 subSysGroups, 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); + +/* check, if FBC-Plugin is available */ +SEXP isAvailableFbcPlugin(); + +/* check, if Groups-Plugin is available */ +SEXP isAvailableGroupsPlugin(); diff --git a/src/symbols.rds b/src/symbols.rds new file mode 100644 index 0000000000000000000000000000000000000000..86d3f8e1d4117ef59178496ee79fda1f4224d930 Binary files /dev/null and b/src/symbols.rds differ