################################################### ### chunk number 1: setup ################################################### #line 85 "vignettes/Rredland/inst/doc/Rredland.Rnw" library(Rredland) gofrag <- system.file("RDF/gopart.rdf", package="Rredland") ################################################### ### chunk number 2: dump ################################################### #line 91 "vignettes/Rredland/inst/doc/Rredland.Rnw" readLines(gofrag,n=10) ################################################### ### chunk number 3: seturi ################################################### #line 99 "vignettes/Rredland/inst/doc/Rredland.Rnw" gouri <- makeRedlURI( paste("file:", gofrag, sep="") ) ################################################### ### chunk number 4: dored1 ################################################### #line 105 "vignettes/Rredland/inst/doc/Rredland.Rnw" gof <- readRDF( gouri ) gof ################################################### ### chunk number 5: lkcls ################################################### #line 110 "vignettes/Rredland/inst/doc/Rredland.Rnw" getClass("redlModel") ################################################### ### chunk number 6: lksiz ################################################### #line 118 "vignettes/Rredland/inst/doc/Rredland.Rnw" #getRedlModelSize(model(gof)) size(gof) ################################################### ### chunk number 7: lkdf ################################################### #line 124 "vignettes/Rredland/inst/doc/Rredland.Rnw" godf <- as(gof, "data.frame") godf[1:4,] ################################################### ### chunk number 8: lkobj ################################################### #line 130 "vignettes/Rredland/inst/doc/Rredland.Rnw" as.character(godf[1:4,3]) ################################################### ### chunk number 9: bypred ################################################### #line 136 "vignettes/Rredland/inst/doc/Rredland.Rnw" bypred <- split(godf, as.character(godf$predicate)) names(bypred) sapply(bypred, nrow) ################################################### ### chunk number 10: lktree ################################################### #line 143 "vignettes/Rredland/inst/doc/Rredland.Rnw" bypred$"http://www.w3.org/2000/01/rdf-schema#subClassOf"[,-2] ################################################### ### chunk number 11: dobp1 ################################################### #line 151 "vignettes/Rredland/inst/doc/Rredland.Rnw" bp1 <- makeRedlURI(paste("file:",system.file("RDF/biopax-level1.owl", package="Rredland"),sep="")) bp1m <- readRDF( bp1 ) size(bp1m) ################################################### ### chunk number 12: lkbp1 ################################################### #line 158 "vignettes/Rredland/inst/doc/Rredland.Rnw" bp1df <- as(bp1m, "data.frame") sapply(bp1df[1:5,], substring, 1, 70) ################################################### ### chunk number 13: defstp ################################################### #line 166 "vignettes/Rredland/inst/doc/Rredland.Rnw" strip2pound <- function(x) gsub(".*#","",cleanXSDT(as.character(x))) sapply(bp1df[1:5,], strip2pound) ################################################### ### chunk number 14: getcl ################################################### #line 173 "vignettes/Rredland/inst/doc/Rredland.Rnw" isTypeOwlClass <- grep("owl#Class", as.character(bp1df[,3])) strip2pound( bp1df[isTypeOwlClass,1] ) ################################################### ### chunk number 15: ################################################### #line 186 "vignettes/Rredland/inst/doc/Rredland.Rnw" chopLong = function(x,nword=12) { tvec <- strsplit(x," ")[[1]] ltvec <- length(tvec) if (ltvec %% nword != 0) { pad <- rep(" ", ceiling(length(tvec))*nword) pad[1:ltvec] <- tvec } else pad <- tvec ss <- matrix(pad,nr=nword) ss <- rbind(ss,"\n") paste(ss,collapse=" ") } ################################################### ### chunk number 16: getcldef ################################################### #line 200 "vignettes/Rredland/inst/doc/Rredland.Rnw" getClassComment <- function(term, df, nsPref="http://www.biopax.org/release/biopax-level1.owl#", commPred= "http://www.w3.org/2000/01/rdf-schema#comment", doChop=TRUE, nword=12 ) { ind <- which( as.character(df[,1]) == paste(nsPref,term,sep="") & as.character(df[,2]) == commPred ) chopLong(cleanXSDT(as.character(bp1df[ind,3])), nword=nword) } cat(getClassComment("chemicalStructure", bp1df )) cat(getClassComment("biochemicalReaction", bp1df )) ################################################### ### chunk number 17: lk2 ################################################### #line 213 "vignettes/Rredland/inst/doc/Rredland.Rnw" bp2 <- makeRedlURI(paste("file:",system.file("RDF/biopax-level2.owl", package="Rredland"),sep="")) bp2m <- readRDF( bp2 ) size(bp2m) bp2df <- as(bp2m, "data.frame") isTypeOwlClass <- grep("owl#Class", as.character(bp2df[,3])) strip2pound( bp2df[isTypeOwlClass,1] ) ################################################### ### chunk number 18: getHum eval=FALSE ################################################### ## #line 233 "vignettes/Rredland/inst/doc/Rredland.Rnw" ## humu <- makeRedlURI(paste("file:","humancyc.owl",sep="")) ## humm <- readRDF( humu, storageType="bdb", storageName="hucyc") ################################################### ### chunk number 19: gethdf eval=FALSE ################################################### ## #line 250 "vignettes/Rredland/inst/doc/Rredland.Rnw" ## hudf <- as(humm, "data.frame") ## husubs <- as.character(hudf[,1]) ## hupreds <- as.character(hudf[,2]) ## huobs <- as.character(hudf[,3]) ## table(hupreds) ################################################### ### chunk number 20: getnpw eval=FALSE ################################################### ## #line 259 "vignettes/Rredland/inst/doc/Rredland.Rnw" ## isPw <- grep("pathway", husubs) ## isNa <- grep("NAME", hupreds) ## isnp <- intersect(isPw, isNa) ## cleanXSDT(huobs[isnp][1:10])