git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@93390 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -10,7 +10,7 @@ Description: GSNAP and GMAP are a pair of tools to align short-read |
10 | 10 |
methods to work with GMAP and GSNAP from within R. In addition, |
11 | 11 |
it provides methods to tally alignment results on a |
12 | 12 |
per-nucleotide basis using the bam_tally tool. |
13 |
-Version: 1.7.6 |
|
13 |
+Version: 1.7.7 |
|
14 | 14 |
Depends: R (>= 2.15.0), methods, GenomeInfoDb (>= 1.1.3), |
15 | 15 |
GenomicRanges (>= 1.17.12) |
16 | 16 |
Imports: S4Vectors, IRanges, Rsamtools (>= 1.17.8), rtracklayer (>= 1.25.5), |
... | ... |
@@ -47,11 +47,12 @@ normArgWhich <- function(x, genome) { |
47 | 47 |
setGeneric("normArgCdsIIT", function(exon_iit, genome, ...) standardGeneric("normArgCdsIIT")) |
48 | 48 |
|
49 | 49 |
setMethod("normArgCdsIIT", "ANY", function(exon_iit, genome, BPPARAM) { |
50 |
- if(!is(exon_iit, "character") || length(exon_iit) > 1) |
|
51 |
- stop("Invalid exon_iit value. Accepted values types are: single character value (file location), GRangesList of exons, a TxDb object (use the exons in the TxDb), or a GmapGenome (use the genome gene map iit)") |
|
52 |
- if(nchar(exon_iit) && !file.exists(exon_iit)) |
|
50 |
+ if(!is.null(exon_iit) && (!is(exon_iit, "character") || length(exon_iit) > 1)) |
|
51 |
+ stop("Invalid exon_iit value. Accepted values types are: single character value (file location), GRangesList of exons, a TxDb object (use the exons in the TxDb), a GmapGenome (use the genome gene map iit), or NULL") |
|
52 |
+ if(!is.null(exon_iit) && (nchar(exon_iit) && !file.exists(exon_iit))) |
|
53 | 53 |
stop("exon_iit is non-empty and does not point to an existing file") |
54 | 54 |
exon_iit |
55 |
+ |
|
55 | 56 |
}) |
56 | 57 |
|
57 | 58 |
setMethod("normArgCdsIIT", "TxDb", function(exon_iit, genome, BPPARAM) { |
... | ... |
@@ -45,13 +45,12 @@ $(SUBDIRS): %: %/Makefile |
45 | 45 |
|
46 | 46 |
gstruct/Makefile: gstruct/configure ${R_SRC_DIR}/samtools |
47 | 47 |
cd $(dir $@); \ |
48 |
- CFLAGS="-g -O0" ./configure --enable-static --disable-shared \ |
|
48 |
+ CFLAGS="-g" ./configure --enable-static --disable-shared \ |
|
49 | 49 |
--prefix=${PREFIX} --includedir=${GSTRUCT_INCLUDE_DIR} \ |
50 | 50 |
--libdir=${PREFIX}/${LIBnn} \ |
51 | 51 |
--with-samtools-lib=${R_SRC_DIR}/samtools \ |
52 | 52 |
--disable-binaries \ |
53 |
-# --disable-maintainer-mode \ |
|
54 |
- #\ added by gabe 5/14/14 |
|
53 |
+ --disable-maintainer-mode \ |
|
55 | 54 |
## does not appear to be a true dependency yet |
56 | 55 |
## --with-gmap=${PREFIX}/bin |
57 | 56 |
|
... | ... |
@@ -79,11 +79,11 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R, |
79 | 79 |
print_indels_p, blocksize, verbosep, |
80 | 80 |
/*readlevel_p*/false, max_softclip, |
81 | 81 |
/* print_xs_scores_p ??? */ false, |
82 |
-// /* print_noncovered_p ??? */ false); |
|
83 |
- /* print_noncovered_p ??? */ true); |
|
82 |
+ /* print_noncovered_p ??? */ false); |
|
84 | 83 |
IIT_free(&chromosome_iit); |
85 | 84 |
Genome_free(&genome); |
86 |
- IIT_free(&map_iit); |
|
85 |
+ if(map_iit != NULL) |
|
86 |
+ IIT_free(&map_iit); |
|
87 | 87 |
if (tally_iit == NULL) { |
88 | 88 |
error("Could not create tally\n"); |
89 | 89 |
} |
... | ... |
@@ -139,6 +139,7 @@ LIBTOOL = @LIBTOOL@ |
139 | 139 |
LIPO = @LIPO@ |
140 | 140 |
LN_S = @LN_S@ |
141 | 141 |
LTLIBOBJS = @LTLIBOBJS@ |
142 |
+MAINT = @MAINT@ |
|
142 | 143 |
MAKEINFO = @MAKEINFO@ |
143 | 144 |
MKDIR_P = @MKDIR_P@ |
144 | 145 |
NM = @NM@ |
... | ... |
@@ -235,7 +236,7 @@ all: all-recursive |
235 | 236 |
.SUFFIXES: |
236 | 237 |
am--refresh: |
237 | 238 |
@: |
238 |
-$(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) |
|
239 |
+$(srcdir)/Makefile.in: @MAINTAINER_MODE_TRUE@ $(srcdir)/Makefile.am $(am__configure_deps) |
|
239 | 240 |
@for dep in $?; do \ |
240 | 241 |
case '$(am__configure_deps)' in \ |
241 | 242 |
*$$dep*) \ |
... | ... |
@@ -262,9 +263,9 @@ Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status |
262 | 263 |
$(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) |
263 | 264 |
$(SHELL) ./config.status --recheck |
264 | 265 |
|
265 |
-$(top_srcdir)/configure: $(am__configure_deps) |
|
266 |
+$(top_srcdir)/configure: @MAINTAINER_MODE_TRUE@ $(am__configure_deps) |
|
266 | 267 |
cd $(srcdir) && $(AUTOCONF) |
267 |
-$(ACLOCAL_M4): $(am__aclocal_m4_deps) |
|
268 |
+$(ACLOCAL_M4): @MAINTAINER_MODE_TRUE@ $(am__aclocal_m4_deps) |
|
268 | 269 |
cd $(srcdir) && $(ACLOCAL) $(ACLOCAL_AMFLAGS) |
269 | 270 |
lib/gstruct-${LIBGSTRUCT_API_VERSION}.pc: $(top_builddir)/config.status $(top_srcdir)/lib/gstruct.pc.in |
270 | 271 |
cd $(top_builddir) && $(SHELL) ./config.status $@ |
... | ... |
@@ -531,6 +531,35 @@ fi |
531 | 531 |
rmdir .tst 2>/dev/null |
532 | 532 |
AC_SUBST([am__leading_dot])]) |
533 | 533 |
|
534 |
+# Add --enable-maintainer-mode option to configure. -*- Autoconf -*- |
|
535 |
+# From Jim Meyering |
|
536 |
+ |
|
537 |
+# Copyright (C) 1996, 1998, 2000, 2001, 2002, 2003, 2004, 2005 |
|
538 |
+# Free Software Foundation, Inc. |
|
539 |
+# |
|
540 |
+# This file is free software; the Free Software Foundation |
|
541 |
+# gives unlimited permission to copy and/or distribute it, |
|
542 |
+# with or without modifications, as long as this notice is preserved. |
|
543 |
+ |
|
544 |
+# serial 4 |
|
545 |
+ |
|
546 |
+AC_DEFUN([AM_MAINTAINER_MODE], |
|
547 |
+[AC_MSG_CHECKING([whether to enable maintainer-specific portions of Makefiles]) |
|
548 |
+ dnl maintainer-mode is disabled by default |
|
549 |
+ AC_ARG_ENABLE(maintainer-mode, |
|
550 |
+[ --enable-maintainer-mode enable make rules and dependencies not useful |
|
551 |
+ (and sometimes confusing) to the casual installer], |
|
552 |
+ USE_MAINTAINER_MODE=$enableval, |
|
553 |
+ USE_MAINTAINER_MODE=no) |
|
554 |
+ AC_MSG_RESULT([$USE_MAINTAINER_MODE]) |
|
555 |
+ AM_CONDITIONAL(MAINTAINER_MODE, [test $USE_MAINTAINER_MODE = yes]) |
|
556 |
+ MAINT=$MAINTAINER_MODE_TRUE |
|
557 |
+ AC_SUBST(MAINT)dnl |
|
558 |
+] |
|
559 |
+) |
|
560 |
+ |
|
561 |
+AU_DEFUN([jm_MAINTAINER_MODE], [AM_MAINTAINER_MODE]) |
|
562 |
+ |
|
534 | 563 |
# Check to see how 'make' treats includes. -*- Autoconf -*- |
535 | 564 |
|
536 | 565 |
# Copyright (C) 2001, 2002, 2003, 2005 Free Software Foundation, Inc. |
... | ... |
@@ -888,6 +888,9 @@ build |
888 | 888 |
LIBGSTRUCT_API_VERSION |
889 | 889 |
LIBGSTRUCT_SO_VERSION |
890 | 890 |
CFLAGS |
891 |
+MAINT |
|
892 |
+MAINTAINER_MODE_FALSE |
|
893 |
+MAINTAINER_MODE_TRUE |
|
891 | 894 |
target_alias |
892 | 895 |
host_alias |
893 | 896 |
build_alias |
... | ... |
@@ -928,6 +931,7 @@ SHELL' |
928 | 931 |
ac_subst_files='' |
929 | 932 |
ac_user_opts=' |
930 | 933 |
enable_option_checking |
934 |
+enable_maintainer_mode |
|
931 | 935 |
enable_largefile |
932 | 936 |
enable_dependency_tracking |
933 | 937 |
enable_fulldist |
... | ... |
@@ -1591,6 +1595,8 @@ Optional Features: |
1591 | 1595 |
--disable-option-checking ignore unrecognized --enable/--with options |
1592 | 1596 |
--disable-FEATURE do not include FEATURE (same as --enable-FEATURE=no) |
1593 | 1597 |
--enable-FEATURE[=ARG] include FEATURE [ARG=yes] |
1598 |
+ --enable-maintainer-mode enable make rules and dependencies not useful |
|
1599 |
+ (and sometimes confusing) to the casual installer |
|
1594 | 1600 |
--disable-largefile omit support for large files |
1595 | 1601 |
--disable-dependency-tracking speeds up one-time build |
1596 | 1602 |
--enable-dependency-tracking do not reject slow dependency extractors |
... | ... |
@@ -2091,6 +2097,33 @@ $as_echo_n "checking package version... " >&6; } |
2091 | 2097 |
{ $as_echo "$as_me:$LINENO: result: 2014-08-05" >&5 |
2092 | 2098 |
$as_echo "2014-08-05" >&6; } |
2093 | 2099 |
|
2100 |
+## Added by gabe to enable "--disable-maintainer-mode" configure argument |
|
2101 |
+## for bioc build machines |
|
2102 |
+{ $as_echo "$as_me:$LINENO: checking whether to enable maintainer-specific portions of Makefiles" >&5 |
|
2103 |
+$as_echo_n "checking whether to enable maintainer-specific portions of Makefiles... " >&6; } |
|
2104 |
+ # Check whether --enable-maintainer-mode was given. |
|
2105 |
+if test "${enable_maintainer_mode+set}" = set; then |
|
2106 |
+ enableval=$enable_maintainer_mode; USE_MAINTAINER_MODE=$enableval |
|
2107 |
+else |
|
2108 |
+ USE_MAINTAINER_MODE=no |
|
2109 |
+fi |
|
2110 |
+ |
|
2111 |
+ { $as_echo "$as_me:$LINENO: result: $USE_MAINTAINER_MODE" >&5 |
|
2112 |
+$as_echo "$USE_MAINTAINER_MODE" >&6; } |
|
2113 |
+ if test $USE_MAINTAINER_MODE = yes; then |
|
2114 |
+ MAINTAINER_MODE_TRUE= |
|
2115 |
+ MAINTAINER_MODE_FALSE='#' |
|
2116 |
+else |
|
2117 |
+ MAINTAINER_MODE_TRUE='#' |
|
2118 |
+ MAINTAINER_MODE_FALSE= |
|
2119 |
+fi |
|
2120 |
+ |
|
2121 |
+ MAINT=$MAINTAINER_MODE_TRUE |
|
2122 |
+ |
|
2123 |
+ |
|
2124 |
+ |
|
2125 |
+ |
|
2126 |
+ |
|
2094 | 2127 |
### Read defaults |
2095 | 2128 |
{ $as_echo "$as_me:$LINENO: checking CONFIG_SITE" >&5 |
2096 | 2129 |
$as_echo_n "checking CONFIG_SITE... " >&6; } |
... | ... |
@@ -5819,13 +5852,13 @@ if test "${lt_cv_nm_interface+set}" = set; then |
5819 | 5852 |
else |
5820 | 5853 |
lt_cv_nm_interface="BSD nm" |
5821 | 5854 |
echo "int some_variable = 0;" > conftest.$ac_ext |
5822 |
- (eval echo "\"\$as_me:5822: $ac_compile\"" >&5) |
|
5855 |
+ (eval echo "\"\$as_me:5855: $ac_compile\"" >&5) |
|
5823 | 5856 |
(eval "$ac_compile" 2>conftest.err) |
5824 | 5857 |
cat conftest.err >&5 |
5825 |
- (eval echo "\"\$as_me:5825: $NM \\\"conftest.$ac_objext\\\"\"" >&5) |
|
5858 |
+ (eval echo "\"\$as_me:5858: $NM \\\"conftest.$ac_objext\\\"\"" >&5) |
|
5826 | 5859 |
(eval "$NM \"conftest.$ac_objext\"" 2>conftest.err > conftest.out) |
5827 | 5860 |
cat conftest.err >&5 |
5828 |
- (eval echo "\"\$as_me:5828: output\"" >&5) |
|
5861 |
+ (eval echo "\"\$as_me:5861: output\"" >&5) |
|
5829 | 5862 |
cat conftest.out >&5 |
5830 | 5863 |
if $GREP 'External.*some_variable' conftest.out > /dev/null; then |
5831 | 5864 |
lt_cv_nm_interface="MS dumpbin" |
... | ... |
@@ -7030,7 +7063,7 @@ ia64-*-hpux*) |
7030 | 7063 |
;; |
7031 | 7064 |
*-*-irix6*) |
7032 | 7065 |
# Find out which ABI we are using. |
7033 |
- echo '#line 7033 "configure"' > conftest.$ac_ext |
|
7066 |
+ echo '#line 7066 "configure"' > conftest.$ac_ext |
|
7034 | 7067 |
if { (eval echo "$as_me:$LINENO: \"$ac_compile\"") >&5 |
7035 | 7068 |
(eval $ac_compile) 2>&5 |
7036 | 7069 |
ac_status=$? |
... | ... |
@@ -8887,11 +8920,11 @@ else |
8887 | 8920 |
-e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ |
8888 | 8921 |
-e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ |
8889 | 8922 |
-e 's:$: $lt_compiler_flag:'` |
8890 |
- (eval echo "\"\$as_me:8890: $lt_compile\"" >&5) |
|
8923 |
+ (eval echo "\"\$as_me:8923: $lt_compile\"" >&5) |
|
8891 | 8924 |
(eval "$lt_compile" 2>conftest.err) |
8892 | 8925 |
ac_status=$? |
8893 | 8926 |
cat conftest.err >&5 |
8894 |
- echo "$as_me:8894: \$? = $ac_status" >&5 |
|
8927 |
+ echo "$as_me:8927: \$? = $ac_status" >&5 |
|
8895 | 8928 |
if (exit $ac_status) && test -s "$ac_outfile"; then |
8896 | 8929 |
# The compiler can only warn and ignore the option if not recognized |
8897 | 8930 |
# So say no if there are warnings other than the usual output. |
... | ... |
@@ -9226,11 +9259,11 @@ else |
9226 | 9259 |
-e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ |
9227 | 9260 |
-e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ |
9228 | 9261 |
-e 's:$: $lt_compiler_flag:'` |
9229 |
- (eval echo "\"\$as_me:9229: $lt_compile\"" >&5) |
|
9262 |
+ (eval echo "\"\$as_me:9262: $lt_compile\"" >&5) |
|
9230 | 9263 |
(eval "$lt_compile" 2>conftest.err) |
9231 | 9264 |
ac_status=$? |
9232 | 9265 |
cat conftest.err >&5 |
9233 |
- echo "$as_me:9233: \$? = $ac_status" >&5 |
|
9266 |
+ echo "$as_me:9266: \$? = $ac_status" >&5 |
|
9234 | 9267 |
if (exit $ac_status) && test -s "$ac_outfile"; then |
9235 | 9268 |
# The compiler can only warn and ignore the option if not recognized |
9236 | 9269 |
# So say no if there are warnings other than the usual output. |
... | ... |
@@ -9331,11 +9364,11 @@ else |
9331 | 9364 |
-e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ |
9332 | 9365 |
-e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ |
9333 | 9366 |
-e 's:$: $lt_compiler_flag:'` |
9334 |
- (eval echo "\"\$as_me:9334: $lt_compile\"" >&5) |
|
9367 |
+ (eval echo "\"\$as_me:9367: $lt_compile\"" >&5) |
|
9335 | 9368 |
(eval "$lt_compile" 2>out/conftest.err) |
9336 | 9369 |
ac_status=$? |
9337 | 9370 |
cat out/conftest.err >&5 |
9338 |
- echo "$as_me:9338: \$? = $ac_status" >&5 |
|
9371 |
+ echo "$as_me:9371: \$? = $ac_status" >&5 |
|
9339 | 9372 |
if (exit $ac_status) && test -s out/conftest2.$ac_objext |
9340 | 9373 |
then |
9341 | 9374 |
# The compiler can only warn and ignore the option if not recognized |
... | ... |
@@ -9386,11 +9419,11 @@ else |
9386 | 9419 |
-e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ |
9387 | 9420 |
-e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ |
9388 | 9421 |
-e 's:$: $lt_compiler_flag:'` |
9389 |
- (eval echo "\"\$as_me:9389: $lt_compile\"" >&5) |
|
9422 |
+ (eval echo "\"\$as_me:9422: $lt_compile\"" >&5) |
|
9390 | 9423 |
(eval "$lt_compile" 2>out/conftest.err) |
9391 | 9424 |
ac_status=$? |
9392 | 9425 |
cat out/conftest.err >&5 |
9393 |
- echo "$as_me:9393: \$? = $ac_status" >&5 |
|
9426 |
+ echo "$as_me:9426: \$? = $ac_status" >&5 |
|
9394 | 9427 |
if (exit $ac_status) && test -s out/conftest2.$ac_objext |
9395 | 9428 |
then |
9396 | 9429 |
# The compiler can only warn and ignore the option if not recognized |
... | ... |
@@ -12186,7 +12219,7 @@ else |
12186 | 12219 |
lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 |
12187 | 12220 |
lt_status=$lt_dlunknown |
12188 | 12221 |
cat > conftest.$ac_ext <<_LT_EOF |
12189 |
-#line 12189 "configure" |
|
12222 |
+#line 12222 "configure" |
|
12190 | 12223 |
#include "confdefs.h" |
12191 | 12224 |
|
12192 | 12225 |
#if HAVE_DLFCN_H |
... | ... |
@@ -12282,7 +12315,7 @@ else |
12282 | 12315 |
lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 |
12283 | 12316 |
lt_status=$lt_dlunknown |
12284 | 12317 |
cat > conftest.$ac_ext <<_LT_EOF |
12285 |
-#line 12285 "configure" |
|
12318 |
+#line 12318 "configure" |
|
12286 | 12319 |
#include "confdefs.h" |
12287 | 12320 |
|
12288 | 12321 |
#if HAVE_DLFCN_H |
... | ... |
@@ -21234,6 +21267,13 @@ LIBOBJS=$ac_libobjs |
21234 | 21267 |
LTLIBOBJS=$ac_ltlibobjs |
21235 | 21268 |
|
21236 | 21269 |
|
21270 |
+if test -z "${MAINTAINER_MODE_TRUE}" && test -z "${MAINTAINER_MODE_FALSE}"; then |
|
21271 |
+ { { $as_echo "$as_me:$LINENO: error: conditional \"MAINTAINER_MODE\" was never defined. |
|
21272 |
+Usually this means the macro was only invoked conditionally." >&5 |
|
21273 |
+$as_echo "$as_me: error: conditional \"MAINTAINER_MODE\" was never defined. |
|
21274 |
+Usually this means the macro was only invoked conditionally." >&2;} |
|
21275 |
+ { (exit 1); exit 1; }; } |
|
21276 |
+fi |
|
21237 | 21277 |
if test -z "${AMDEP_TRUE}" && test -z "${AMDEP_FALSE}"; then |
21238 | 21278 |
{ { $as_echo "$as_me:$LINENO: error: conditional \"AMDEP\" was never defined. |
21239 | 21279 |
Usually this means the macro was only invoked conditionally." >&5 |
... | ... |
@@ -20,6 +20,12 @@ AC_INIT([gstruct],PKG_VERSION,[Thomas Wu <twu@gene.com>]) |
20 | 20 |
AC_MSG_CHECKING(package version) |
21 | 21 |
AC_MSG_RESULT(PKG_VERSION) |
22 | 22 |
|
23 |
+## Added by gabe to enable "--disable-maintainer-mode" configure argument |
|
24 |
+## for bioc build machines |
|
25 |
+AM_MAINTAINER_MODE([enable]) |
|
26 |
+ |
|
27 |
+ |
|
28 |
+ |
|
23 | 29 |
### Read defaults |
24 | 30 |
AC_MSG_CHECKING(CONFIG_SITE) |
25 | 31 |
if test -z "$CONFIG_SITE"; then |
... | ... |
@@ -250,6 +250,7 @@ LIBTOOL = @LIBTOOL@ |
250 | 250 |
LIPO = @LIPO@ |
251 | 251 |
LN_S = @LN_S@ |
252 | 252 |
LTLIBOBJS = @LTLIBOBJS@ |
253 |
+MAINT = @MAINT@ |
|
253 | 254 |
MAKEINFO = @MAKEINFO@ |
254 | 255 |
MKDIR_P = @MKDIR_P@ |
255 | 256 |
NM = @NM@ |
... | ... |
@@ -411,7 +412,7 @@ all: config.h |
411 | 412 |
|
412 | 413 |
.SUFFIXES: |
413 | 414 |
.SUFFIXES: .c .lo .o .obj |
414 |
-$(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) |
|
415 |
+$(srcdir)/Makefile.in: @MAINTAINER_MODE_TRUE@ $(srcdir)/Makefile.am $(am__configure_deps) |
|
415 | 416 |
@for dep in $?; do \ |
416 | 417 |
case '$(am__configure_deps)' in \ |
417 | 418 |
*$$dep*) \ |
... | ... |
@@ -436,9 +437,9 @@ Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status |
436 | 437 |
$(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) |
437 | 438 |
cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh |
438 | 439 |
|
439 |
-$(top_srcdir)/configure: $(am__configure_deps) |
|
440 |
+$(top_srcdir)/configure: @MAINTAINER_MODE_TRUE@ $(am__configure_deps) |
|
440 | 441 |
cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh |
441 |
-$(ACLOCAL_M4): $(am__aclocal_m4_deps) |
|
442 |
+$(ACLOCAL_M4): @MAINTAINER_MODE_TRUE@ $(am__aclocal_m4_deps) |
|
442 | 443 |
cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh |
443 | 444 |
|
444 | 445 |
config.h: stamp-h1 |
... | ... |
@@ -450,7 +451,7 @@ config.h: stamp-h1 |
450 | 451 |
stamp-h1: $(srcdir)/config.h.in $(top_builddir)/config.status |
451 | 452 |
@rm -f stamp-h1 |
452 | 453 |
cd $(top_builddir) && $(SHELL) ./config.status src/config.h |
453 |
-$(srcdir)/config.h.in: $(am__configure_deps) |
|
454 |
+$(srcdir)/config.h.in: @MAINTAINER_MODE_TRUE@ $(am__configure_deps) |
|
454 | 455 |
cd $(top_srcdir) && $(AUTOHEADER) |
455 | 456 |
rm -f stamp-h1 |
456 | 457 |
touch $@ |