Browse code

various hacks to get the source code updater to work for me

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@110047 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 28/10/2015 20:56:15
Showing 1 changed files
... ...
@@ -11,20 +11,19 @@
11 11
 # through svn).
12 12
 ##########################################################
13 13
 
14
-fixMakefile = function() {
14
+enableMaintainerMode = function() {
15 15
     mkfile = file.path("src/Makefile")
16 16
     txt = readLines(mkfile)
17 17
     txt2 = gsub("(--disable-maintainer-mode.*)", "\\\\ # \\1;", txt)
18 18
     writeLines(txt2, con = mkfile)
19 19
 }
20 20
 
21
-unfixMakefile = function() {
21
+disableMaintainerMode = function() {
22 22
     mkfile = file.path("src/Makefile")
23 23
     txt = readLines(mkfile)
24 24
     txt2 = gsub("\\\\ # (.*);", "\\1", txt)
25 25
     writeLines(txt2, con = mkfile)
26 26
 }
27
-    
28 27
 
29 28
 updateGMAPSrc <- function() {
30 29
 
... ...
@@ -60,13 +59,14 @@ updateGSTRUCTSrc <- function() {
60 59
   if (file.exists(extractDir)) {
61 60
     unlink(extractDir, recursive=TRUE)
62 61
   }
63
-  dir.create(extractDir)
62
+  dir.create(extractDir, recursive=TRUE)
64 63
   
65 64
   svnCheckoutDir <- .getSVNProj(projectSVNURL, extractDir)
66 65
   on.exit(unlink(svnCheckoutDir, recursive=TRUE), add=TRUE)
67 66
   setwd(svnCheckoutDir)
68
-  .bootstrapSVNCheckout(bootstrap.script)  
69
-  .configureSrc(program)
67
+  .bootstrapSVNCheckout(bootstrap.script)
68
+  samtoolsPath <- file.path(startingDir, "src", "samtools")
69
+  .configureSrc(program, samtoolsPath)
70 70
   .makeDist()
71 71
   .extractDistTarballIntoSrcDirectory(extractDir)
72 72
   invisible(TRUE)
... ...
@@ -107,12 +107,17 @@ updateGSTRUCTSrc <- function() {
107 107
   }
108 108
 }
109 109
 
110
-.configureSrc <- function(program) {
110
+.configureSrc <- function(program, samtoolsPath = NULL) {
111 111
   ##--with-gmapdb=${GMAPDB} --prefix=${PREFIX}
112 112
   ##configure. Set
113 113
   ##run a "make dist" to build a tarball
114 114
   command <- "./configure --disable-fulldist"
115
-  ##if (program == "gstruct") command <- paste(command, "--disable-binaries")
115
+  if (!is.null(samtoolsPath)) {
116
+      command <- paste0(command, " --with-samtools-lib=", samtoolsPath)
117
+  }
118
+  if (program == "gstruct") {
119
+      command <- paste(command, "--disable-binaries")
120
+  }
116 121
   if (!system(command) == 0) {
117 122
     stop("unable to configure")
118 123
   }
... ...
@@ -127,10 +132,7 @@ updateGSTRUCTSrc <- function() {
127 132
 }
128 133
 
129 134
 .makeDist <- function() {
130
-  ##run a "make dist" to build a tarball
131
-  if (!system("make distcheck") == 0) {
132
-    stop("unable to 'make dist'")
133
-  }  
135
+    system("make && make dist") ## possibly more robust than direct "make dist"
134 136
 }
135 137
 
136 138
 .extractDistTarballIntoSrcDirectory <- function(extractDir) {
Browse code

gstruct should always use trunk

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@104077 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 21/05/2015 23:14:49
Showing 1 changed files
... ...
@@ -38,7 +38,7 @@ updateGMAPSrc <- function() {
38 38
 }
39 39
 updateGSTRUCTSrc <- function() {
40 40
   #gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/releases/internal-2014-04-09"
41
-    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/branches/2014-07-10-amino-acid-tally"
41
+    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
42 42
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
43 43
   .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
44 44
                        extractDir=extractDirGstruct,
Browse code

Reverted to r101133, along with NAMESPACE fixes

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@102487 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 14/04/2015 21:40:44
Showing 1 changed files
... ...
@@ -38,7 +38,7 @@ updateGMAPSrc <- function() {
38 38
 }
39 39
 updateGSTRUCTSrc <- function() {
40 40
   #gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/releases/internal-2014-04-09"
41
-    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
41
+    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/branches/2014-07-10-amino-acid-tally"
42 42
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
43 43
   .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
44 44
                        extractDir=extractDirGstruct,
Browse code

update gstruct/bamtally

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@101176 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 25/03/2015 20:25:05
Showing 1 changed files
... ...
@@ -38,7 +38,7 @@ updateGMAPSrc <- function() {
38 38
 }
39 39
 updateGSTRUCTSrc <- function() {
40 40
   #gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/releases/internal-2014-04-09"
41
-    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/branches/2014-07-10-amino-acid-tally"
41
+    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
42 42
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
43 43
   .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
44 44
                        extractDir=extractDirGstruct,
Browse code

add codon tally support. No vbump yet

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@93316 bc3139a8-67e5-0310-9ffc-ced21a209358

Gabriel Becker authored on 11/08/2014 23:42:48
Showing 1 changed files
... ...
@@ -8,12 +8,28 @@
8 8
 # "--disable-maintainer-mode" argument passed in src/Makefile to the
9 9
 # respective configure scripts. This was added to avoid regenerating
10 10
 # autotools artifacts on user machines (the timestamp protection fails
11
-# through svn). ALSO make sure not to remove the maintainer mode macro call
12
-# in gstruct|gmap/configure.ac (revert the change from the update).
11
+# through svn).
13 12
 ##########################################################
14 13
 
14
+fixMakefile = function() {
15
+    mkfile = file.path("src/Makefile")
16
+    txt = readLines(mkfile)
17
+    txt2 = gsub("(--disable-maintainer-mode.*)", "\\\\ # \\1;", txt)
18
+    writeLines(txt2, con = mkfile)
19
+}
20
+
21
+unfixMakefile = function() {
22
+    mkfile = file.path("src/Makefile")
23
+    txt = readLines(mkfile)
24
+    txt2 = gsub("\\\\ # (.*);", "\\1", txt)
25
+    writeLines(txt2, con = mkfile)
26
+}
27
+    
28
+
15 29
 updateGMAPSrc <- function() {
16
-  gmapSVNProj <-
30
+
31
+    mkfile = 
32
+    gmapSVNProj <-
17 33
     "http://resscm/bioinfo/projects/gmap/releases/internal-2013-10-01"
18 34
   extractDirGmap <- file.path(getwd(), "src/gmap")
19 35
   .bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
... ...
@@ -21,7 +37,8 @@ updateGMAPSrc <- function() {
21 37
   
22 38
 }
23 39
 updateGSTRUCTSrc <- function() {
24
-  gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
40
+  #gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/releases/internal-2014-04-09"
41
+    gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/branches/2014-07-10-amino-acid-tally"
25 42
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
26 43
   .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
27 44
                        extractDir=extractDirGstruct,
Browse code

update to new bam_tally with support for XS counting, which we now support via BamTallyParam@count_xs.

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@90225 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 13/05/2014 02:04:05
Showing 1 changed files
... ...
@@ -8,7 +8,8 @@
8 8
 # "--disable-maintainer-mode" argument passed in src/Makefile to the
9 9
 # respective configure scripts. This was added to avoid regenerating
10 10
 # autotools artifacts on user machines (the timestamp protection fails
11
-# through svn).
11
+# through svn). ALSO make sure not to remove the maintainer mode macro call
12
+# in gstruct|gmap/configure.ac (revert the change from the update).
12 13
 ##########################################################
13 14
 
14 15
 updateGMAPSrc <- function() {
Browse code

update GMAP/GSNAP to 2013-10-1 branch; MAJOR optimizations.

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@88339 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 02/04/2014 21:21:47
Showing 1 changed files
... ...
@@ -13,7 +13,7 @@
13 13
 
14 14
 updateGMAPSrc <- function() {
15 15
   gmapSVNProj <-
16
-    "http://resscm/bioinfo/projects/gmap/releases/public-2013-03-31"
16
+    "http://resscm/bioinfo/projects/gmap/releases/internal-2013-10-01"
17 17
   extractDirGmap <- file.path(getwd(), "src/gmap")
18 18
   .bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
19 19
                        program="gmap", bootstrap = "bootstrap.gsnaptoo")
Browse code

some guidance for updating GMAP/GSTRUCT source code

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@79764 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 23/08/2013 14:24:34
Showing 1 changed files
... ...
@@ -1,5 +1,16 @@
1 1
 ##run this to update. The current working directory needs to be the
2 2
 ##top-level directory of the SVN checkout
3
+
4
+#########################################################
5
+## PLEASE READ
6
+##########################################################
7
+# When building a new version of gstruct/gmap, remove the
8
+# "--disable-maintainer-mode" argument passed in src/Makefile to the
9
+# respective configure scripts. This was added to avoid regenerating
10
+# autotools artifacts on user machines (the timestamp protection fails
11
+# through svn).
12
+##########################################################
13
+
3 14
 updateGMAPSrc <- function() {
4 15
   gmapSVNProj <-
5 16
     "http://resscm/bioinfo/projects/gmap/releases/public-2013-03-31"
Browse code

fixes for GMAP/GSTRUCT source code updater

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@78424 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 14/07/2013 00:37:35
Showing 1 changed files
... ...
@@ -2,10 +2,10 @@
2 2
 ##top-level directory of the SVN checkout
3 3
 updateGMAPSrc <- function() {
4 4
   gmapSVNProj <-
5
-    "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
5
+    "http://resscm/bioinfo/projects/gmap/releases/public-2013-03-31"
6 6
   extractDirGmap <- file.path(getwd(), "src/gmap")
7 7
   .bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
8
-                       program="gmap")
8
+                       program="gmap", bootstrap = "bootstrap.gsnaptoo")
9 9
   
10 10
 }
11 11
 updateGSTRUCTSrc <- function() {
... ...
@@ -13,7 +13,8 @@ updateGSTRUCTSrc <- function() {
13 13
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
14 14
   .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
15 15
                        extractDir=extractDirGstruct,
16
-                       program="gstruct")
16
+                       program="gstruct",
17
+                       bootstrap = "bootstrap.Rdist")
17 18
   .copySamflagsHeader(extractDirGstruct, file.path(getwd(), "src/gmap"))
18 19
 }
19 20
 
... ...
@@ -21,7 +22,9 @@ updateGSTRUCTSrc <- function() {
21 22
 ###helper functions
22 23
 ###################
23 24
 
24
-.bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
25
+.bootstrapAndExtract <- function(projectSVNURL, extractDir, program,
26
+                                 bootstrap.script)
27
+{
25 28
   startingDir <- getwd()
26 29
   on.exit(setwd(startingDir))
27 30
 
... ...
@@ -33,7 +36,7 @@ updateGSTRUCTSrc <- function() {
33 36
   svnCheckoutDir <- .getSVNProj(projectSVNURL, extractDir)
34 37
   on.exit(unlink(svnCheckoutDir, recursive=TRUE), add=TRUE)
35 38
   setwd(svnCheckoutDir)
36
-  .bootstrapSVNCheckout()  
39
+  .bootstrapSVNCheckout(bootstrap.script)  
37 40
   .configureSrc(program)
38 41
   .makeDist()
39 42
   .extractDistTarballIntoSrcDirectory(extractDir)
... ...
@@ -69,8 +72,8 @@ updateGSTRUCTSrc <- function() {
69 72
 }
70 73
 
71 74
 ##assumes in the correct dir
72
-.bootstrapSVNCheckout <- function() {
73
-  if (!system("./bootstrap.Rdist") == 0) {
75
+.bootstrapSVNCheckout <- function(bootstrap.script) {
76
+  if (!system(paste0("./", bootstrap.script)) == 0) {
74 77
     stop("unable to bootstrap")
75 78
   }
76 79
 }
Browse code

refactor GMAP/GSTRUCT code import to allow updating GMAP and GSTRUCT separately. Some other fixes.

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@74872 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 26/03/2013 21:39:20
Showing 1 changed files
... ...
@@ -1,17 +1,20 @@
1 1
 ##run this to update. The current working directory needs to be the
2 2
 ##top-level directory of the SVN checkout
3
-updateGMAPRSrc <- function() {
4
-  gmapSVNProj <- "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
5
-  gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
6
-
3
+updateGMAPSrc <- function() {
4
+  gmapSVNProj <-
5
+    "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
7 6
   extractDirGmap <- file.path(getwd(), "src/gmap")
8
-  extractDirGstruct <- file.path(getwd(), "src/gstruct")
9
-
10 7
   .bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
11
-                      program="gmap")  
12
-  .bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
13
-                      program="gstruct")
14
-  .copySamflagsHeader(extractDirGstruct, extractDirGmap)
8
+                       program="gmap")
9
+  
10
+}
11
+updateGSTRUCTSrc <- function() {
12
+  gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
13
+  extractDirGstruct <- file.path(getwd(), "src/gstruct")
14
+  .bootstrapAndExtract(projectSVNURL=gstructSVNProj,
15
+                       extractDir=extractDirGstruct,
16
+                       program="gstruct")
17
+  .copySamflagsHeader(extractDirGstruct, file.path(getwd(), "src/gmap"))
15 18
 }
16 19
 
17 20
 ###################
Browse code

added new version of gmap and gstruct src code

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@70363 bc3139a8-67e5-0310-9ffc-ced21a209358

Cory Barr authored on 10/10/2012 00:38:59
Showing 1 changed files
... ...
@@ -7,14 +7,18 @@ updateGMAPRSrc <- function() {
7 7
   extractDirGmap <- file.path(getwd(), "src/gmap")
8 8
   extractDirGstruct <- file.path(getwd(), "src/gstruct")
9 9
 
10
-  bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
10
+  .bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
11 11
                       program="gmap")  
12
-  bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
12
+  .bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
13 13
                       program="gstruct")
14 14
   .copySamflagsHeader(extractDirGstruct, extractDirGmap)
15 15
 }
16
-  
17
-bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
16
+
17
+###################
18
+###helper functions
19
+###################
20
+
21
+.bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
18 22
   startingDir <- getwd()
19 23
   on.exit(setwd(startingDir))
20 24
 
... ...
@@ -33,10 +37,6 @@ bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
33 37
   invisible(TRUE)
34 38
 }
35 39
 
36
-###################
37
-###helper functions
38
-###################
39
-
40 40
 .copySamflagsHeader <- function(extractDirGstruct, extractDirGmap) {
41 41
   ##gstruct needs samflags.h. Copying from the gmap src
42 42
   gstructSamflagsLoc <- file.path(extractDirGstruct, "src/samflags.h")
Browse code

if replacing src files for GMAP, GSNAP, GSTRUCT, previous src directory is completely deleting prior to re-adding src

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@70173 bc3139a8-67e5-0310-9ffc-ced21a209358

Cory Barr authored on 04/10/2012 00:12:03
Showing 1 changed files
... ...
@@ -18,6 +18,11 @@ bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
18 18
   startingDir <- getwd()
19 19
   on.exit(setwd(startingDir))
20 20
 
21
+  if (file.exists(extractDir)) {
22
+    unlink(extractDir, recursive=TRUE)
23
+  }
24
+  dir.create(extractDir)
25
+  
21 26
   svnCheckoutDir <- .getSVNProj(projectSVNURL, extractDir)
22 27
   on.exit(unlink(svnCheckoutDir, recursive=TRUE), add=TRUE)
23 28
   setwd(svnCheckoutDir)
... ...
@@ -67,7 +72,6 @@ bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
67 72
   }
68 73
 }
69 74
 
70
-
71 75
 .configureSrc <- function(program) {
72 76
   ##--with-gmapdb=${GMAPDB} --prefix=${PREFIX}
73 77
   ##configure. Set
Browse code

updated script to add GMAP/GSNAP/GSTRUCT src from SVN repo

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@70171 bc3139a8-67e5-0310-9ffc-ced21a209358

Cory Barr authored on 03/10/2012 23:02:14
Showing 1 changed files
... ...
@@ -1,26 +1,74 @@
1
-bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
1
+##run this to update. The current working directory needs to be the
2
+##top-level directory of the SVN checkout
3
+updateGMAPRSrc <- function() {
4
+  gmapSVNProj <- "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
5
+  gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
6
+
7
+  extractDirGmap <- file.path(getwd(), "src/gmap")
8
+  extractDirGstruct <- file.path(getwd(), "src/gstruct")
2 9
 
10
+  bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
11
+                      program="gmap")  
12
+  bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
13
+                      program="gstruct")
14
+  .copySamflagsHeader(extractDirGstruct, extractDirGmap)
15
+}
16
+  
17
+bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
3 18
   startingDir <- getwd()
4 19
   on.exit(setwd(startingDir))
5
-  
20
+
21
+  svnCheckoutDir <- .getSVNProj(projectSVNURL, extractDir)
22
+  on.exit(unlink(svnCheckoutDir, recursive=TRUE), add=TRUE)
23
+  setwd(svnCheckoutDir)
24
+  .bootstrapSVNCheckout()  
25
+  .configureSrc(program)
26
+  .makeDist()
27
+  .extractDistTarballIntoSrcDirectory(extractDir)
28
+  invisible(TRUE)
29
+}
30
+
31
+###################
32
+###helper functions
33
+###################
34
+
35
+.copySamflagsHeader <- function(extractDirGstruct, extractDirGmap) {
36
+  ##gstruct needs samflags.h. Copying from the gmap src
37
+  gstructSamflagsLoc <- file.path(extractDirGstruct, "src/samflags.h")
38
+  if (!file.exists(gstructSamflagsLoc)) {
39
+    
40
+    gmapSamflagsLoc <- file.path(extractDirGmap, "src/samflags.h")  
41
+    if (!file.exists(gmapSamflagsLoc)) {
42
+      stop("Could not find the samflags.h file in the gmap src code")
43
+    }
44
+    
45
+    file.copy(gmapSamflagsLoc, gstructSamflagsLoc)
46
+  }
47
+}
48
+
49
+.getSVNProj <- function(projectSVNURL, extractDir) {
6 50
   ##grab from svn
7 51
   tmpDir <- file.path(tempdir(), basename(extractDir))
8 52
   dir.create(tmpDir, recursive=TRUE)
9
-  on.exit(unlink(tmpDir, recursive=TRUE), add=TRUE)
10
-  
11 53
   command <- paste("svn co",
12 54
                    projectSVNURL,
13 55
                    tmpDir)
14 56
   if (!system(command) == 0) {
15 57
     stop("Could not check out project from SVN")
16 58
   }
17
-    
18
-  ##bootstrap it
19
-  setwd(tmpDir)
59
+
60
+  return(tmpDir)
61
+}
62
+
63
+##assumes in the correct dir
64
+.bootstrapSVNCheckout <- function() {
20 65
   if (!system("./bootstrap.Rdist") == 0) {
21 66
     stop("unable to bootstrap")
22 67
   }
68
+}
69
+
23 70
 
71
+.configureSrc <- function(program) {
24 72
   ##--with-gmapdb=${GMAPDB} --prefix=${PREFIX}
25 73
   ##configure. Set
26 74
   ##run a "make dist" to build a tarball
... ...
@@ -37,22 +85,29 @@ bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
37 85
       system("touch config.site")
38 86
     }
39 87
   }
40
-  
88
+}
89
+
90
+.makeDist <- function() {
41 91
   ##run a "make dist" to build a tarball
42 92
   if (!system("make distcheck") == 0) {
43 93
     stop("unable to 'make dist'")
44 94
   }  
45
-  
95
+}
96
+
97
+.extractDistTarballIntoSrcDirectory <- function(extractDir) {
46 98
   ##extract tarball into 'src' directory of package
47
-  distTarball <- dir(pattern="*\\.tar\\.gz$")
99
+  distTarball <- dir(pattern="*\\.tar\\.gz$", full.names=TRUE)
48 100
   if (length(distTarball) > 1) {
49 101
     stop("Found more than one tarball in directory. ",
50 102
          "Not sure which is the distribution. Aborting.")
51 103
   }
52
-  if (!file.exists(extractDir)) {
53
-    dir.create(extractDir, recursive=TRUE)
104
+  distTarball <- tools::file_path_as_absolute(distTarball)
105
+  if (file.exists(extractDir)) {
106
+    unlink(extractDir, recursive=TRUE)
54 107
   }
55
-  distName <- sub("\\..*", "", distTarball)
108
+  dir.create(extractDir, recursive=TRUE)
109
+
110
+  distName <- sub("\\..*", "", basename(distTarball))
56 111
   command <- paste("tar xvf", distTarball,
57 112
                    "-C",
58 113
                    extractDir,
... ...
@@ -71,31 +126,4 @@ bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
71 126
     stop("Could not move extracted directory down one level")
72 127
   }
73 128
   unlink(whereTarExtracted, recursive=TRUE)
74
-
75
-  invisible(TRUE)
76
-}
77
-
78
-options(error=recover)
79
-
80
-gmapSVNProj <- "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
81
-extractDirGmap <- file.path(getwd(), "src/gmap")
82
-bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
83
-                    program="gmap")
84
-
85
-gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
86
-extractDirGstruct <- file.path(getwd(), "src/gstruct")
87
-bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
88
-                    program="gstruct")
89
-
90
-##gstruct needs samflags.h. Copying from the gmap src
91
-gstructSamflagsLoc <- file.path(extractDirGstruct, "src/samflags.h")
92
-if (!file.exists(gstructSamflagsLoc)) {
93
- 
94
-  gmapSamflagsLoc <- file.path(extractDirGmap, "src/samflags.h")  
95
-  if (!file.exists(gmapSamflagsLoc)) {
96
-    stop("Could not find the samflags.h file in the gmap src code")
97
-  }
98
-
99
-  file.copy(gmapSamflagsLoc, gstructSamflagsLoc)
100 129
 }
101
-    
Browse code

moving script to update GMAP and gstruct source code to scripts dir

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@68571 bc3139a8-67e5-0310-9ffc-ced21a209358

Cory Barr authored on 17/08/2012 23:09:24
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,101 @@
1
+bootstrapAndExtract <- function(projectSVNURL, extractDir, program) {
2
+
3
+  startingDir <- getwd()
4
+  on.exit(setwd(startingDir))
5
+  
6
+  ##grab from svn
7
+  tmpDir <- file.path(tempdir(), basename(extractDir))
8
+  dir.create(tmpDir, recursive=TRUE)
9
+  on.exit(unlink(tmpDir, recursive=TRUE), add=TRUE)
10
+  
11
+  command <- paste("svn co",
12
+                   projectSVNURL,
13
+                   tmpDir)
14
+  if (!system(command) == 0) {
15
+    stop("Could not check out project from SVN")
16
+  }
17
+    
18
+  ##bootstrap it
19
+  setwd(tmpDir)
20
+  if (!system("./bootstrap.Rdist") == 0) {
21
+    stop("unable to bootstrap")
22
+  }
23
+
24
+  ##--with-gmapdb=${GMAPDB} --prefix=${PREFIX}
25
+  ##configure. Set
26
+  ##run a "make dist" to build a tarball
27
+  command <- "./configure --disable-fulldist"
28
+  ##if (program == "gstruct") command <- paste(command, "--disable-binaries")
29
+  if (!system(command) == 0) {
30
+    stop("unable to configure")
31
+  }
32
+
33
+  ##gstruct SVN repo doesn't have config.site (this code needs to work
34
+  ##today)
35
+  if (program == "gstruct") {
36
+    if (!file.exists("config.site")) {
37
+      system("touch config.site")
38
+    }
39
+  }
40
+  
41
+  ##run a "make dist" to build a tarball
42
+  if (!system("make distcheck") == 0) {
43
+    stop("unable to 'make dist'")
44
+  }  
45
+  
46
+  ##extract tarball into 'src' directory of package
47
+  distTarball <- dir(pattern="*\\.tar\\.gz$")
48
+  if (length(distTarball) > 1) {
49
+    stop("Found more than one tarball in directory. ",
50
+         "Not sure which is the distribution. Aborting.")
51
+  }
52
+  if (!file.exists(extractDir)) {
53
+    dir.create(extractDir, recursive=TRUE)
54
+  }
55
+  distName <- sub("\\..*", "", distTarball)
56
+  command <- paste("tar xvf", distTarball,
57
+                   "-C",
58
+                   extractDir,
59
+                   distName)
60
+  if (!system(command) == 0) {
61
+    stop("Could not extract source from distribution into specified directory.")
62
+  }
63
+
64
+  ##move contents of untarred dir up one level
65
+  ##TODO: How (or can) you do this w/ a tar command?
66
+  whereTarExtracted <- file.path(extractDir, distName)
67
+  command <- paste("mv",
68
+                   paste0(whereTarExtracted, "/*"),
69
+                   extractDir)
70
+  if (!system(command) == 0) {
71
+    stop("Could not move extracted directory down one level")
72
+  }
73
+  unlink(whereTarExtracted, recursive=TRUE)
74
+
75
+  invisible(TRUE)
76
+}
77
+
78
+options(error=recover)
79
+
80
+gmapSVNProj <- "http://resscm/bioinfo/projects/gmap/branches/internal-2011-12-28"
81
+extractDirGmap <- file.path(getwd(), "src/gmap")
82
+bootstrapAndExtract(projectSVNURL=gmapSVNProj, extractDir=extractDirGmap,
83
+                    program="gmap")
84
+
85
+gstructSVNProj <- "http://resscm/bioinfo/projects/gstruct/trunk"
86
+extractDirGstruct <- file.path(getwd(), "src/gstruct")
87
+bootstrapAndExtract(projectSVNURL=gstructSVNProj, extractDir=extractDirGstruct,
88
+                    program="gstruct")
89
+
90
+##gstruct needs samflags.h. Copying from the gmap src
91
+gstructSamflagsLoc <- file.path(extractDirGstruct, "src/samflags.h")
92
+if (!file.exists(gstructSamflagsLoc)) {
93
+ 
94
+  gmapSamflagsLoc <- file.path(extractDirGmap, "src/samflags.h")  
95
+  if (!file.exists(gmapSamflagsLoc)) {
96
+    stop("Could not find the samflags.h file in the gmap src code")
97
+  }
98
+
99
+  file.copy(gmapSamflagsLoc, gstructSamflagsLoc)
100
+}
101
+