ad42d27c |
##run this to update. The current working directory needs to be the
##top-level directory of the SVN checkout
|
af9250b2 |
#########################################################
## PLEASE READ
##########################################################
# When building a new version of gstruct/gmap, remove the
# "--disable-maintainer-mode" argument passed in src/Makefile to the
# respective configure scripts. This was added to avoid regenerating
# autotools artifacts on user machines (the timestamp protection fails
|
c78be696 |
# through svn).
|
af9250b2 |
##########################################################
|
a5e05187 |
enableMaintainerMode = function() {
|
c78be696 |
mkfile = file.path("src/Makefile")
txt = readLines(mkfile)
txt2 = gsub("(--disable-maintainer-mode.*)", "\\\\ # \\1;", txt)
writeLines(txt2, con = mkfile)
}
|
a5e05187 |
disableMaintainerMode = function() {
|
c78be696 |
mkfile = file.path("src/Makefile")
txt = readLines(mkfile)
txt2 = gsub("\\\\ # (.*);", "\\1", txt)
writeLines(txt2, con = mkfile)
}
|
70241617 |
updateGMAPSrc <- function() {
|
c78be696 |
mkfile =
gmapSVNProj <-
|
35ef8171 |
"http://resscm/bioinfo/projects/gmap/releases/internal-2013-10-01"
|
ad42d27c |
extractDirGmap <- file.path(getwd(), "src/gmap")
|
36cb64f8 |
.bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
|
b458ffe2 |
program="gmap", bootstrap = "bootstrap.gsnaptoo")
|
70241617 |
}
updateGSTRUCTSrc <- function() {
|
c78be696 |
#gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/releases/internal-2014-04-09"
|
7fce6e2d |
gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
|
70241617 |
extractDirGstruct <- file.path(getwd(), "src/gstruct")
.bootstrapAndExtract(projectSVNURL=gstructSVNProj,
extractDir=extractDirGstruct,
|
b458ffe2 |
program="gstruct",
bootstrap = "bootstrap.Rdist")
|
70241617 |
.copySamflagsHeader(extractDirGstruct, file.path(getwd(), "src/gmap"))
|
ad42d27c |
}
|
36cb64f8 |
###################
###helper functions
###################
|
b458ffe2 |
.bootstrapAndExtract <- function(projectSVNURL, extractDir, program,
bootstrap.script)
{
|
b22faf0d |
startingDir <- getwd()
on.exit(setwd(startingDir))
|
ad42d27c |
|
ed798423 |
if (file.exists(extractDir)) {
unlink(extractDir, recursive=TRUE)
}
|
a5e05187 |
dir.create(extractDir, recursive=TRUE)
|
ed798423 |
|
ad42d27c |
svnCheckoutDir <- .getSVNProj(projectSVNURL, extractDir)
on.exit(unlink(svnCheckoutDir, recursive=TRUE), add=TRUE)
setwd(svnCheckoutDir)
|
a5e05187 |
.bootstrapSVNCheckout(bootstrap.script)
samtoolsPath <- file.path(startingDir, "src", "samtools")
.configureSrc(program, samtoolsPath)
|
ad42d27c |
.makeDist()
.extractDistTarballIntoSrcDirectory(extractDir)
invisible(TRUE)
}
.copySamflagsHeader <- function(extractDirGstruct, extractDirGmap) {
##gstruct needs samflags.h. Copying from the gmap src
gstructSamflagsLoc <- file.path(extractDirGstruct, "src/samflags.h")
if (!file.exists(gstructSamflagsLoc)) {
gmapSamflagsLoc <- file.path(extractDirGmap, "src/samflags.h")
if (!file.exists(gmapSamflagsLoc)) {
stop("Could not find the samflags.h file in the gmap src code")
}
file.copy(gmapSamflagsLoc, gstructSamflagsLoc)
}
}
.getSVNProj <- function(projectSVNURL, extractDir) {
|
b22faf0d |
##grab from svn
tmpDir <- file.path(tempdir(), basename(extractDir))
dir.create(tmpDir, recursive=TRUE)
command <- paste("svn co",
projectSVNURL,
tmpDir)
if (!system(command) == 0) {
stop("Could not check out project from SVN")
}
|
ad42d27c |
return(tmpDir)
}
##assumes in the correct dir
|
b458ffe2 |
.bootstrapSVNCheckout <- function(bootstrap.script) {
if (!system(paste0("./", bootstrap.script)) == 0) {
|
b22faf0d |
stop("unable to bootstrap")
}
|
ad42d27c |
}
|
a5e05187 |
.configureSrc <- function(program, samtoolsPath = NULL) {
|
b22faf0d |
##--with-gmapdb=${GMAPDB} --prefix=${PREFIX}
##configure. Set
##run a "make dist" to build a tarball
command <- "./configure --disable-fulldist"
|
a5e05187 |
if (!is.null(samtoolsPath)) {
command <- paste0(command, " --with-samtools-lib=", samtoolsPath)
}
if (program == "gstruct") {
command <- paste(command, "--disable-binaries")
}
|
b22faf0d |
if (!system(command) == 0) {
stop("unable to configure")
}
##gstruct SVN repo doesn't have config.site (this code needs to work
##today)
if (program == "gstruct") {
if (!file.exists("config.site")) {
system("touch config.site")
}
}
|
ad42d27c |
}
.makeDist <- function() {
|
a5e05187 |
system("make && make dist") ## possibly more robust than direct "make dist"
|
ad42d27c |
}
.extractDistTarballIntoSrcDirectory <- function(extractDir) {
|
b22faf0d |
##extract tarball into 'src' directory of package
|
ad42d27c |
distTarball <- dir(pattern="*\\.tar\\.gz$", full.names=TRUE)
|
b22faf0d |
if (length(distTarball) > 1) {
stop("Found more than one tarball in directory. ",
"Not sure which is the distribution. Aborting.")
}
|
ad42d27c |
distTarball <- tools::file_path_as_absolute(distTarball)
if (file.exists(extractDir)) {
unlink(extractDir, recursive=TRUE)
|
b22faf0d |
}
|
ad42d27c |
dir.create(extractDir, recursive=TRUE)
distName <- sub("\\..*", "", basename(distTarball))
|
b22faf0d |
command <- paste("tar xvf", distTarball,
"-C",
extractDir,
distName)
if (!system(command) == 0) {
stop("Could not extract source from distribution into specified directory.")
}
##move contents of untarred dir up one level
##TODO: How (or can) you do this w/ a tar command?
whereTarExtracted <- file.path(extractDir, distName)
command <- paste("mv",
paste0(whereTarExtracted, "/*"),
extractDir)
if (!system(command) == 0) {
stop("Could not move extracted directory down one level")
}
unlink(whereTarExtracted, recursive=TRUE)
}
|