git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/CoGAPS@57772 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
Package: CoGAPS |
2 |
-Version: 1.3.0 |
|
2 |
+Version: 1.3.1 |
|
3 | 3 |
Date: 2010-07-02 |
4 | 4 |
Title: Coordinated Gene Activity in Pattern Sets |
5 | 5 |
Author: Elana J. Fertig |
... | ... |
@@ -10,9 +10,9 @@ Description: Coordinated Gene Activity in Pattern Sets (CoGAPS) infers |
10 | 10 |
inferring activity on gene sets. |
11 | 11 |
Maintainer: Elana J. Fertig <ejfertig@jhmi.edu>, Michael F. Ochs <mfo@jhu.edu> |
12 | 12 |
SystemRequirements: GAPS-JAGS (==1.0.2) |
13 |
-Depends: R (>= 2.9.0), rjags(>= 2.1.0), R.utils (>= 1.2.4) |
|
13 |
+Depends: R (>= 2.9.0), R.utils (>= 1.2.4) |
|
14 | 14 |
Imports: graphics, grDevices, methods, stats, utils |
15 | 15 |
License: GPL (== 2) |
16 |
-URL: http://www.cancerbiostats.onc.jhmi.edu/cogaps.cfm |
|
16 |
+URL: http://www.cancerbiostats.onc.jhmi.edu/CoGAPS.cfm |
|
17 | 17 |
biocViews: GeneExpression, Microarray, Bioinformatics |
18 | 18 |
|
... | ... |
@@ -2,9 +2,16 @@ export(CoGAPS) |
2 | 2 |
export(GAPS) |
3 | 3 |
export(calcCoGAPSStat) |
4 | 4 |
export(plotGAPS) |
5 |
+if(tools:::.OStype() == "windows") { |
|
6 |
+importFrom(utils, readRegistry, winProgressBar, setWinProgressBar) |
|
7 |
+} |
|
8 |
+importFrom(utils, txtProgressBar, setTxtProgressBar) |
|
9 |
+importFrom(stats, variable.names, sd, update) |
|
5 | 10 |
importFrom(graphics, matplot, title) |
6 | 11 |
importFrom(grDevices, dev.new, dev.off, pdf) |
7 | 12 |
importFrom(methods, is) |
8 |
-importFrom(rjags, jags.model, load.module, jags.samples) |
|
9 | 13 |
importFrom(stats, heatmap, runif) |
10 | 14 |
importFrom(utils, read.table, write.table) |
15 |
+S3method(coef, jags) |
|
16 |
+S3method(update, jags) |
|
17 |
+S3method(variable.names, jags) |
... | ... |
@@ -1,2 +1,3 @@ |
1 |
-CoGAPS requires GAPS-JAGS available from http://www.cancerbiostats.onc.jhmi.edu/cogaps.cfm. This c++ package is a redistribution of JAGS version 2.1.0 with a module implementing the GAPS matrix decomposition for microarray data. GAPS-JAGS takes the place of the original JAGS package required for the successful installation and running of the rjags package. Please see the installation instructions in the users manual. If you have any questions, please comment Elana Fertig <ejfertig@jhmi.edu> or Michael Ochs <mfo@jhu.edu>. |
|
1 |
+CoGAPS requires GAPS-JAGS available from http://www.cancerbiostats.onc.jhmi.edu/cogaps.cfm. This c++ package is a redistribution of JAGS version 2.1.0 with a module implementing the GAPS matrix decomposition for microarray data. Please see the installation instructions in the users manual. If you have any questions, please comment Elana Fertig <ejfertig@jhmi.edu> or Michael Ochs <mfo@jhu.edu>. |
|
2 | 2 |
|
3 |
+01Sep2011 - Removed dependency on rjags package on CRAN |
... | ... |
@@ -5,9 +5,6 @@ RunGAPS <- function(data, unc, numPatterns, |
5 | 5 |
SAIter, iter, thin=1) { |
6 | 6 |
|
7 | 7 |
|
8 |
- # load in the matrix decomposition module |
|
9 |
- load.module(c("gaps")) |
|
10 |
- |
|
11 | 8 |
# get the data needed for MCMC |
12 | 9 |
matrixDecompData <- GetDataListGAPS(data, unc, numPatterns, |
13 | 10 |
MaxAtomsA, alphaA, lambdaA, |
14 | 11 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,362 @@ |
1 |
+jags.model <- function(file, data=sys.frame(sys.parent()), inits, |
|
2 |
+ n.chains = 1, n.adapt=1000, nchain) |
|
3 |
+{ |
|
4 |
+ |
|
5 |
+ if (missing(file)) { |
|
6 |
+ stop("Model file name missing") |
|
7 |
+ } |
|
8 |
+ if (!file.exists(file)) { |
|
9 |
+ stop(paste("Model file \"", file, "\" not found", sep="")) |
|
10 |
+ } |
|
11 |
+ if (!missing(nchain)) { |
|
12 |
+ warning("Argument nchain in jags.model is deprecated. Use n.chains.") |
|
13 |
+ if (missing(n.chains)) { |
|
14 |
+ n.chains = nchain |
|
15 |
+ } |
|
16 |
+ } |
|
17 |
+ |
|
18 |
+ p <- .Call("make_console", PACKAGE="CoGAPS") |
|
19 |
+ .Call("check_model", p, file, PACKAGE="CoGAPS") |
|
20 |
+ |
|
21 |
+ varnames <- .Call("get_variable_names", p, PACKAGE="CoGAPS") |
|
22 |
+ if (is.environment(data)) { |
|
23 |
+ ##Get a list of numeric objects from the supplied environment |
|
24 |
+ data <- mget(varnames, envir=data, mode="numeric", |
|
25 |
+ ifnotfound=list(NULL)) |
|
26 |
+ ##Strip null entries |
|
27 |
+ data <- data[!sapply(data, is.null)] |
|
28 |
+ } |
|
29 |
+ else if (is.list(data)) { |
|
30 |
+ v <- names(data) |
|
31 |
+ if (is.null(v)) { |
|
32 |
+ stop("data must be a named list") |
|
33 |
+ } |
|
34 |
+ if (any(nchar(v)==0)) { |
|
35 |
+ stop("unnamed variables in data list") |
|
36 |
+ } |
|
37 |
+ if (any(duplicated(v))) { |
|
38 |
+ stop("Duplicated names in data list: ", |
|
39 |
+ paste(v[duplicated(v)], collapse=" ")) |
|
40 |
+ } |
|
41 |
+ relevant.variables <- v %in% varnames |
|
42 |
+ data <- data[relevant.variables] |
|
43 |
+ unused.variables <- setdiff(v, varnames) |
|
44 |
+ for (i in seq(along=unused.variables)) { |
|
45 |
+ warning("Unused variable \"", unused.variables[i], "\" in data") |
|
46 |
+ } |
|
47 |
+ } |
|
48 |
+ else { |
|
49 |
+ stop("data must be a list or environment") |
|
50 |
+ } |
|
51 |
+ |
|
52 |
+ .Call("compile", p, data, as.integer(n.chains), TRUE, PACKAGE="CoGAPS") |
|
53 |
+ |
|
54 |
+### Setting initial values |
|
55 |
+ |
|
56 |
+ if (!missing(inits)) { |
|
57 |
+ |
|
58 |
+ checkParameters <- function(inits) { |
|
59 |
+ if(!is.list(inits)) |
|
60 |
+ return (FALSE) |
|
61 |
+ |
|
62 |
+ inames <- names(inits) |
|
63 |
+ if (is.null(inames) || any(nchar(inames) == 0)) |
|
64 |
+ return (FALSE) |
|
65 |
+ |
|
66 |
+ if (any(duplicated(inames))) |
|
67 |
+ return (FALSE) |
|
68 |
+ |
|
69 |
+ if (any(inames==".RNG.name")) { |
|
70 |
+ rngname <- inits[[".RNG.name"]] |
|
71 |
+ if (!is.character(rngname) || length(rngname) != 1) |
|
72 |
+ return (FALSE) |
|
73 |
+ inits[[".RNG.name"]] <- NULL |
|
74 |
+ } |
|
75 |
+ |
|
76 |
+ if (!all(sapply(inits, is.numeric))) |
|
77 |
+ return (FALSE) |
|
78 |
+ |
|
79 |
+ return (TRUE) |
|
80 |
+ } |
|
81 |
+ |
|
82 |
+ setParameters <- function(inits, chain) { |
|
83 |
+ if (!is.null(inits[[".RNG.name"]])) { |
|
84 |
+ .Call("set_rng_name", p, inits[[".RNG.name"]], |
|
85 |
+ as.integer(chain), PACKAGE="CoGAPS") |
|
86 |
+ inits[[".RNG.name"]] <- NULL |
|
87 |
+ } |
|
88 |
+ .Call("set_parameters", p, inits, as.integer(chain), |
|
89 |
+ PACKAGE="CoGAPS") |
|
90 |
+ } |
|
91 |
+ |
|
92 |
+ init.values <- vector("list", n.chains) |
|
93 |
+ |
|
94 |
+ if (is.function(inits)) { |
|
95 |
+ if (any(names(formals(inits)) == "chain")) { |
|
96 |
+ for (i in 1:n.chains) { |
|
97 |
+ init.values[[i]] <- inits(chain=i) |
|
98 |
+ } |
|
99 |
+ } |
|
100 |
+ else { |
|
101 |
+ for (i in 1:n.chains) { |
|
102 |
+ init.values[[i]] <- inits() |
|
103 |
+ } |
|
104 |
+ } |
|
105 |
+ } |
|
106 |
+ else if (is.list(inits)) { |
|
107 |
+ |
|
108 |
+ if (checkParameters(inits)) { |
|
109 |
+ ## Replicate initial values for all chains |
|
110 |
+ for (i in 1:n.chains) { |
|
111 |
+ init.values[[i]] <- inits |
|
112 |
+ } |
|
113 |
+ } |
|
114 |
+ else { |
|
115 |
+ if (length(inits) != n.chains) { |
|
116 |
+ stop("Length mismatch in inits") |
|
117 |
+ } |
|
118 |
+ init.values <- inits |
|
119 |
+ } |
|
120 |
+ } |
|
121 |
+ |
|
122 |
+ for (i in 1:n.chains) { |
|
123 |
+ if (!checkParameters(init.values[[i]])) { |
|
124 |
+ stop("Invalid parameters for chain ", i) |
|
125 |
+ } |
|
126 |
+ setParameters(init.values[[i]], i) |
|
127 |
+ } |
|
128 |
+ } |
|
129 |
+ |
|
130 |
+ .Call("initialize", p, PACKAGE="CoGAPS") |
|
131 |
+ |
|
132 |
+ model.state <- .Call("get_state", p, PACKAGE="CoGAPS") |
|
133 |
+ model.data <- .Call("get_data", p, PACKAGE="CoGAPS") |
|
134 |
+ model.code <- readLines(file, warn=FALSE) |
|
135 |
+ model <- list("ptr" = function() {p}, |
|
136 |
+ "data" = function() {model.data}, |
|
137 |
+ "model" = function() {model.code}, |
|
138 |
+ "state" = function(internal=FALSE) |
|
139 |
+ { |
|
140 |
+ if(!internal) { |
|
141 |
+ for(i in 1:n.chains) { |
|
142 |
+ model.state[[i]][[".RNG.state"]] <- NULL |
|
143 |
+ model.state[[i]][[".RNG.name"]] <- NULL |
|
144 |
+ } |
|
145 |
+ } |
|
146 |
+ return(model.state) |
|
147 |
+ }, |
|
148 |
+ "nchain" = function() |
|
149 |
+ { |
|
150 |
+ .Call("get_nchain", p, PACKAGE="CoGAPS") |
|
151 |
+ }, |
|
152 |
+ "iter" = function() |
|
153 |
+ { |
|
154 |
+ .Call("get_iter", p, PACKAGE="CoGAPS") |
|
155 |
+ }, |
|
156 |
+ "sync" = function() { |
|
157 |
+ |
|
158 |
+ model.state <<- .Call("get_state", p, PACKAGE="CoGAPS") |
|
159 |
+ }, |
|
160 |
+ "recompile" = function() { |
|
161 |
+ ## Clear the console |
|
162 |
+ .Call("clear_console", p, PACKAGE="CoGAPS") |
|
163 |
+ p <<- .Call("make_console", PACKAGE="CoGAPS") |
|
164 |
+ ## Write the model to a temporary file so we can re-read it |
|
165 |
+ mf <- tempfile() |
|
166 |
+ writeLines(model.code, mf) |
|
167 |
+ .Call("check_model", p, mf, PACKAGE="CoGAPS") |
|
168 |
+ unlink(mf) |
|
169 |
+ ## Re-compile |
|
170 |
+ .Call("compile", p, data, n.chains, FALSE, PACKAGE="CoGAPS") |
|
171 |
+ ## Re-initialize |
|
172 |
+ if (!is.null(model.state)) { |
|
173 |
+ if (length(model.state) != n.chains) { |
|
174 |
+ stop("Incorrect number of chains in saved state") |
|
175 |
+ } |
|
176 |
+ for (i in 1:n.chains) { |
|
177 |
+ statei <- model.state[[i]] |
|
178 |
+ rng <- statei[[".RNG.name"]] |
|
179 |
+ if (!is.null(rng)) { |
|
180 |
+ .Call("set_rng_name", p, rng, i, PACKAGE="CoGAPS") |
|
181 |
+ statei[[".RNG.name"]] <- NULL |
|
182 |
+ } |
|
183 |
+ .Call("set_parameters", p, statei, i, PACKAGE="CoGAPS") |
|
184 |
+ } |
|
185 |
+ .Call("initialize", p, PACKAGE="CoGAPS") |
|
186 |
+ ## Redo adaptation |
|
187 |
+ adapting <- .Call("is_adapting", p, PACKAGE="CoGAPS") |
|
188 |
+ if(n.adapt > 0 && adapting) { |
|
189 |
+ cat("Adapting\n") |
|
190 |
+ .Call("update", p, n.adapt, PACKAGE="CoGAPS") |
|
191 |
+ if (!.Call("adapt_off", p, PACKAGE="CoGAPS")) { |
|
192 |
+ warning("Adaptation incomplete"); |
|
193 |
+ } |
|
194 |
+ } |
|
195 |
+ model.state <<- .Call("get_state", p, PACKAGE="CoGAPS") |
|
196 |
+ } |
|
197 |
+ invisible(NULL) |
|
198 |
+ }) |
|
199 |
+ class(model) <- "jags" |
|
200 |
+ |
|
201 |
+ if (n.adapt > 0) { |
|
202 |
+ adapt(model, n.adapt) |
|
203 |
+ } |
|
204 |
+ return(model) |
|
205 |
+} |
|
206 |
+ |
|
207 |
+parse.varname <- function(varname) { |
|
208 |
+ |
|
209 |
+ ## Try to parse string of form "a" or "a[n,p:q,r]" where "a" is a |
|
210 |
+ ## variable name and n,p,q,r are integers |
|
211 |
+ |
|
212 |
+ v <- try(parse(text=varname, n=1), silent=TRUE) |
|
213 |
+ if (!is.expression(v) || length(v) != 1) |
|
214 |
+ return(NULL) |
|
215 |
+ |
|
216 |
+ v <- v[[1]] |
|
217 |
+ if (is.name(v)) { |
|
218 |
+ ##Full node array requested |
|
219 |
+ return(list(name=deparse(v))) |
|
220 |
+ } |
|
221 |
+ else if (is.call(v) && identical(deparse(v[[1]]), "[") && length(v) > 2) { |
|
222 |
+ ##Subset requested |
|
223 |
+ ndim <- length(v) - 2 |
|
224 |
+ lower <- upper <- numeric(ndim) |
|
225 |
+ if (any(nchar(sapply(v, deparse)) == 0)) { |
|
226 |
+ ##We have to catch empty indices here or they will cause trouble |
|
227 |
+ ##below |
|
228 |
+ return(NULL) |
|
229 |
+ } |
|
230 |
+ for (i in 1:ndim) { |
|
231 |
+ index <- v[[i+2]] |
|
232 |
+ if (is.numeric(index)) { |
|
233 |
+ ##Single index |
|
234 |
+ lower[i] <- upper[i] <- index |
|
235 |
+ } |
|
236 |
+ else if (is.call(index) && length(index) == 3 && |
|
237 |
+ identical(deparse(index[[1]]), ":") && |
|
238 |
+ is.numeric(index[[2]]) && is.numeric(index[[3]])) |
|
239 |
+ { |
|
240 |
+ ##Index range |
|
241 |
+ lower[i] <- index[[2]] |
|
242 |
+ upper[i] <- index[[3]] |
|
243 |
+ } |
|
244 |
+ else return(NULL) |
|
245 |
+ } |
|
246 |
+ if (any(upper < lower)) |
|
247 |
+ return (NULL) |
|
248 |
+ return(list(name = deparse(v[[2]]), lower=lower, upper=upper)) |
|
249 |
+ } |
|
250 |
+ return(NULL) |
|
251 |
+} |
|
252 |
+ |
|
253 |
+parse.varnames <- function(varnames) |
|
254 |
+{ |
|
255 |
+ names <- character(length(varnames)) |
|
256 |
+ lower <- upper <- vector("list", length(varnames)) |
|
257 |
+ for (i in seq(along=varnames)) { |
|
258 |
+ y <- parse.varname(varnames[i]) |
|
259 |
+ if (is.null(y)) { |
|
260 |
+ stop(paste("Invalid variable subset", varnames[i])) |
|
261 |
+ } |
|
262 |
+ names[i] <- y$name |
|
263 |
+ if (!is.null(y$lower)) { |
|
264 |
+ lower[[i]] <- y$lower |
|
265 |
+ } |
|
266 |
+ if (!is.null(y$upper)) { |
|
267 |
+ upper[[i]] <- y$upper |
|
268 |
+ } |
|
269 |
+ } |
|
270 |
+ return(list(names=names, lower=lower, upper=upper)) |
|
271 |
+} |
|
272 |
+ |
|
273 |
+ |
|
274 |
+jags.samples <- |
|
275 |
+ function(model, variable.names, n.iter, thin=1, type="trace", ...) |
|
276 |
+{ |
|
277 |
+ if (class(model) != "jags") |
|
278 |
+ stop("Invalid JAGS model") |
|
279 |
+ |
|
280 |
+ if (!is.character(variable.names) || length(variable.names) == 0) |
|
281 |
+ stop("variable.names must be a character vector") |
|
282 |
+ |
|
283 |
+ if (!is.numeric(n.iter) || length(n.iter) != 1 || n.iter <= 0) |
|
284 |
+ stop("n.iter must be a positive integer") |
|
285 |
+ if (!is.character(type)) |
|
286 |
+ stop("type must be a character vector") |
|
287 |
+ |
|
288 |
+ pn <- parse.varnames(variable.names) |
|
289 |
+ .Call("set_monitors", model$ptr(), pn$names, pn$lower, pn$upper, |
|
290 |
+ as.integer(thin), type, PACKAGE="CoGAPS") |
|
291 |
+ update(model, n.iter, ...) |
|
292 |
+ ans <- .Call("get_monitored_values", model$ptr(), type, PACKAGE="CoGAPS") |
|
293 |
+ for (i in seq(along=variable.names)) { |
|
294 |
+ .Call("clear_monitor", model$ptr(), pn$names[i], pn$lower[[i]], |
|
295 |
+ pn$upper[[i]], type, PACKAGE="CoGAPS") |
|
296 |
+ } |
|
297 |
+ return(ans) |
|
298 |
+} |
|
299 |
+ |
|
300 |
+nchain <- function(model) |
|
301 |
+{ |
|
302 |
+ if (!inherits(model, "jags")) |
|
303 |
+ stop("Invalid JAGS model object in nchain") |
|
304 |
+ |
|
305 |
+ .Call("get_nchain", model$ptr(), PACKAGE="CoGAPS") |
|
306 |
+} |
|
307 |
+ |
|
308 |
+load.module <- function(name, path, quiet=FALSE) |
|
309 |
+{ |
|
310 |
+ if (name %in% list.modules()) { |
|
311 |
+ ## This is a stop-gap measure as JAGS 2.1.0 does allow you |
|
312 |
+ ## to load the same module twice. This should be fixed in |
|
313 |
+ ## later versions. |
|
314 |
+ return(invisible()) #Module already loaded |
|
315 |
+ } |
|
316 |
+ |
|
317 |
+ if (missing(path)) { |
|
318 |
+ path = getOption("jags.moddir") |
|
319 |
+ if (is.null(path)) { |
|
320 |
+ stop("option jags.moddir is not set") |
|
321 |
+ } |
|
322 |
+ } |
|
323 |
+ if (!is.character(path) || length(path) != 1) |
|
324 |
+ stop("invalid path") |
|
325 |
+ if (!is.character(name) || length(name) != 1) |
|
326 |
+ stop("invalid name") |
|
327 |
+ |
|
328 |
+ file <- file.path(path, paste(name, .Platform$dynlib.ext, sep="")) |
|
329 |
+ if (!file.exists(file)) { |
|
330 |
+ stop("File not found: ", file) |
|
331 |
+ } |
|
332 |
+ if (!isDLLLoaded(file)) { |
|
333 |
+ ## We must avoid calling dyn.load twice on the same DLL This |
|
334 |
+ ## may result in the DLL being unloaded and then reloaded, |
|
335 |
+ ## which will invalidate pointers to the distributions, |
|
336 |
+ ## functions and factories in the module. |
|
337 |
+ dyn.load(file) |
|
338 |
+ } |
|
339 |
+ ok <- .Call("load_module", name, PACKAGE="CoGAPS") |
|
340 |
+ if (!ok) { |
|
341 |
+ stop("module", name, "not found\n", sep=" ") |
|
342 |
+ } |
|
343 |
+ else if (!quiet) { |
|
344 |
+ cat("module", name, "loaded\n", sep=" ") |
|
345 |
+ } |
|
346 |
+ invisible() |
|
347 |
+} |
|
348 |
+ |
|
349 |
+list.modules <- function() |
|
350 |
+{ |
|
351 |
+ .Call("get_modules", PACKAGE="CoGAPS"); |
|
352 |
+} |
|
353 |
+ |
|
354 |
+isDLLLoaded <- function(file) |
|
355 |
+{ |
|
356 |
+ dll.list <- getLoadedDLLs() |
|
357 |
+ for (i in seq(along=dll.list)) { |
|
358 |
+ if (dll.list[[i]]["path"][1] == file) |
|
359 |
+ return(TRUE) |
|
360 |
+ } |
|
361 |
+ return(FALSE) |
|
362 |
+} |
0 | 363 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,89 @@ |
1 |
+update.jags <- function(object, n.iter = 1, by, progress.bar, ...) |
|
2 |
+{ |
|
3 |
+ if (!is.numeric(n.iter) || n.iter < 1) { |
|
4 |
+ stop("Invalid n.iter") |
|
5 |
+ } |
|
6 |
+ |
|
7 |
+ if ("update" %in% names(object)) { |
|
8 |
+ ## Old-style jags.model object |
|
9 |
+ ## The progress bar was created by the object$update() function |
|
10 |
+ |
|
11 |
+ if (missing(by)) |
|
12 |
+ by <- floor(n.iter/50) |
|
13 |
+ |
|
14 |
+ object$update(n.iter, by) |
|
15 |
+ } |
|
16 |
+ else { |
|
17 |
+ ## New jags.model object (in version 1.0.3-6) |
|
18 |
+ |
|
19 |
+ adapting <- .Call("is_adapting", object$ptr(), PACKAGE="CoGAPS") |
|
20 |
+ on.exit(object$sync()) |
|
21 |
+ |
|
22 |
+ if (missing(progress.bar)) { |
|
23 |
+ progress.bar <- getOption("jags.pb") |
|
24 |
+ } |
|
25 |
+ if (!is.null(progress.bar)) { |
|
26 |
+ match.arg(progress.bar, c("text","gui","none")) |
|
27 |
+ if (progress.bar=="none") |
|
28 |
+ progress.bar <- NULL |
|
29 |
+ } |
|
30 |
+ |
|
31 |
+ do.pb <- interactive() && !is.null(progress.bar) && n.iter >= 100 |
|
32 |
+ if (do.pb) { |
|
33 |
+ start.iter <- object$iter() |
|
34 |
+ end.iter <- start.iter + n.iter |
|
35 |
+ pb <- switch(progress.bar, |
|
36 |
+ "text" = txtProgressBar(start.iter, end.iter, |
|
37 |
+ initial = start.iter, style=3, width=50, |
|
38 |
+ char=ifelse(adapting,"+","*")), |
|
39 |
+ "gui" = updatePB(start.iter, end.iter, adapting)) |
|
40 |
+ } |
|
41 |
+ |
|
42 |
+ ## Set refresh frequency for progress bar |
|
43 |
+ if (missing(by) || by <= 0) { |
|
44 |
+ by <- min(ceiling(n.iter/50), 100) |
|
45 |
+ } |
|
46 |
+ else { |
|
47 |
+ by <- ceiling(by) |
|
48 |
+ } |
|
49 |
+ |
|
50 |
+ ## Do updates |
|
51 |
+ n <- n.iter |
|
52 |
+ while (n > 0) { |
|
53 |
+ .Call("update", object$ptr(), min(n,by), PACKAGE="CoGAPS") |
|
54 |
+ if (do.pb) { |
|
55 |
+ switch(progress.bar, |
|
56 |
+ "text" = setTxtProgressBar(pb, object$iter()), |
|
57 |
+ "gui" = setPB(pb, object$iter())) |
|
58 |
+ } |
|
59 |
+ n <- n - by |
|
60 |
+ } |
|
61 |
+ if (do.pb) { |
|
62 |
+ close(pb) |
|
63 |
+ } |
|
64 |
+ } |
|
65 |
+ |
|
66 |
+ invisible(NULL) |
|
67 |
+} |
|
68 |
+ |
|
69 |
+adapt <- function(object, n.iter, ...) |
|
70 |
+{ |
|
71 |
+ if(.Call("is_adapting", object$ptr(), PACKAGE="CoGAPS")) { |
|
72 |
+ update(object, n.iter, ...) |
|
73 |
+ if (!.Call("adapt_off", object$ptr(), PACKAGE="CoGAPS")) { |
|
74 |
+ warning("Adaptation incomplete. Recreate the model with a longer adaptive phase.") |
|
75 |
+ } |
|
76 |
+ } |
|
77 |
+ invisible(NULL) |
|
78 |
+} |
|
79 |
+ |
|
80 |
+coef.jags <- function(object, chain = 1, ...) { |
|
81 |
+ if (!is.numeric(chain) || chain < 1 || chain > object$nchain()) { |
|
82 |
+ stop("Invalid chain") |
|
83 |
+ } |
|
84 |
+ object$state(internal=FALSE)[[chain]] |
|
85 |
+} |
|
86 |
+ |
|
87 |
+variable.names.jags <- function(object, ...) { |
|
88 |
+ .Call("get_variable_names", object$ptr(), PACKAGE="CoGAPS") |
|
89 |
+} |
0 | 90 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,26 @@ |
1 |
+read.data <- function(file, format=c("jags","bugs")) |
|
2 |
+{ |
|
3 |
+ format <- match.arg(format) |
|
4 |
+ switch(format, "jags"=read.jagsdata(file), "bugs"=read.bugsdata(file)) |
|
5 |
+} |
|
6 |
+ |
|
7 |
+read.jagsdata <- function(file) |
|
8 |
+{ |
|
9 |
+ e <- new.env() |
|
10 |
+ eval(parse(file), e) |
|
11 |
+ return(as.list(e)) |
|
12 |
+} |
|
13 |
+ |
|
14 |
+read.bugsdata <- function(file) |
|
15 |
+{ |
|
16 |
+ bugs.dat <- dget(file) |
|
17 |
+ for (n in names(bugs.dat)) { |
|
18 |
+ if (!is.null(dim(bugs.dat[[n]]))) { |
|
19 |
+ dim(bugs.dat[[n]]) <- rev(dim(bugs.dat[[n]])) |
|
20 |
+ bugs.dat[[n]] <- aperm(bugs.dat[[n]]) |
|
21 |
+ } |
|
22 |
+ } |
|
23 |
+ return(bugs.dat) |
|
24 |
+} |
|
25 |
+ |
|
26 |
+ |
0 | 27 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,11 @@ |
1 |
+updatePB <- function(start.iter, end.iter, adapting) |
|
2 |
+{ |
|
3 |
+ tcltk:::tkProgressBar(title=ifelse(adapting, "Adapting","Updating"), |
|
4 |
+ label="Iteration 0", min = start.iter, max=end.iter, |
|
5 |
+ initial=start.iter) |
|
6 |
+} |
|
7 |
+ |
|
8 |
+setPB <- function(pb, iter) |
|
9 |
+{ |
|
10 |
+ tcltk:::setTkProgressBar(pb, iter, label=paste("Iteration",iter)) |
|
11 |
+} |
0 | 12 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,20 @@ |
1 |
+.onLoad <- function(lib, pkg) |
|
2 |
+{ |
|
3 |
+ ## Load the rjags wrapper ... |
|
4 |
+ library.dynam("CoGAPS", pkg, lib, local=FALSE) |
|
5 |
+ |
|
6 |
+ ## ... and the modules |
|
7 |
+ moddir <- "/usr/local/lib/JAGS/modules-1.0.2" |
|
8 |
+ if (is.null(getOption("jags.moddir"))) { |
|
9 |
+ options("jags.moddir" = moddir) |
|
10 |
+ } |
|
11 |
+ load.module("basemod") |
|
12 |
+ load.module("gaps") |
|
13 |
+ |
|
14 |
+ .Call("init_jags_console", PACKAGE="CoGAPS") |
|
15 |
+ |
|
16 |
+ ## Set progress bar type |
|
17 |
+ if (is.null(getOption("jags.pb"))) { |
|
18 |
+ options("jags.pb"="text") |
|
19 |
+ } |
|
20 |
+} |
0 | 21 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,20 @@ |
1 |
+.onLoad <- function(lib, pkg) |
|
2 |
+{ |
|
3 |
+ ## Load the rjags wrapper ... |
|
4 |
+ library.dynam("CoGAPS", pkg, lib, local=FALSE) |
|
5 |
+ |
|
6 |
+ ## ... and the modules |
|
7 |
+ moddir <- "@JAGS_MODULES@" |
|
8 |
+ if (is.null(getOption("jags.moddir"))) { |
|
9 |
+ options("jags.moddir" = moddir) |
|
10 |
+ } |
|
11 |
+ load.module("basemod") |
|
12 |
+ load.module("gaps") |
|
13 |
+ |
|
14 |
+ .Call("init_jags_console", PACKAGE="CoGAPS") |
|
15 |
+ |
|
16 |
+ ## Set progress bar type |
|
17 |
+ if (is.null(getOption("jags.pb"))) { |
|
18 |
+ options("jags.pb"="text") |
|
19 |
+ } |
|
20 |
+} |
0 | 21 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,11 @@ |
1 |
+updatePB <- function(start.iter, end.iter, adapting) |
|
2 |
+{ |
|
3 |
+ winProgressBar(title=ifelse(adapting, "Adapting","Updating"), |
|
4 |
+ label="Iteration 0", min = start.iter, max=end.iter, |
|
5 |
+ initial=start.iter) |
|
6 |
+} |
|
7 |
+ |
|
8 |
+setPB <- function(pb, iter) |
|
9 |
+{ |
|
10 |
+ setWinProgressBar(pb, iter, label=paste("Iteration",iter)) |
|
11 |
+} |
0 | 12 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,54 @@ |
1 |
+.onLoad <- function(lib, pkg) |
|
2 |
+{ |
|
3 |
+### First task is to get installation directory of JAGS |
|
4 |
+ |
|
5 |
+ ## Try environment variable first |
|
6 |
+ jags.home <- Sys.getenv("JAGS_HOME") |
|
7 |
+ if (nchar(jags.home)==0) { |
|
8 |
+ keyname <- "SOFTWARE\\JAGS\\JAGS-2.1.0" |
|
9 |
+ if (identical(.Platform$r_arch, "x64")) { |
|
10 |
+ keyname <- paste(keyname,"-x64", sep="") |
|
11 |
+ } |
|
12 |
+ ## Look for multi-user installation in registry |
|
13 |
+ regkey <- try(readRegistry(keyname, hive = "HLM", maxdepth = 1), |
|
14 |
+ silent = TRUE) |
|
15 |
+ if (inherits(regkey, "try-error")) { |
|
16 |
+ ## Look for single-user installation in registry |
|
17 |
+ regkey <- try(readRegistry(keyname, hive = "HCU", maxdepth = 1), |
|
18 |
+ silent = TRUE) |
|
19 |
+ } |
|
20 |
+ if (inherits(regkey, "try-error") || is.null(regkey[["InstallDir"]])) { |
|
21 |
+ ## Give up |
|
22 |
+ stop("Failed to locate JAGS 2.1.0 installation.") |
|
23 |
+ } |
|
24 |
+ jags.home <- regkey[["InstallDir"]] |
|
25 |
+ } |
|
26 |
+ |
|
27 |
+ |
|
28 |
+### Add jags.home to the windows PATH, if not already present |
|
29 |
+ |
|
30 |
+ bindir <- file.path(jags.home, "bin") |
|
31 |
+ path <- Sys.getenv("PATH") |
|
32 |
+ split.path <- strsplit(path, .Platform$path.sep)$PATH |
|
33 |
+ if (!any(split.path == bindir)) { |
|
34 |
+ path <- paste(bindir, path, sep=.Platform$path.sep) |
|
35 |
+ Sys.setenv("PATH"=path) |
|
36 |
+ } |
|
37 |
+ |
|
38 |
+### Set the module directory, if the option jags.moddir is not already set |
|
39 |
+ |
|
40 |
+ if (is.null(getOption("jags.moddir"))) { |
|
41 |
+ options("jags.moddir" = file.path(jags.home, "modules")) |
|
42 |
+ } |
|
43 |
+ library.dynam("CoGAPS", pkg, lib, local=FALSE) |
|
44 |
+ load.module("basemod") |
|
45 |
+ load.module("gaps") |
|
46 |
+ |
|
47 |
+ .Call("init_jags_console", PACKAGE="CoGAPS") |
|
48 |
+ |
|
49 |
+### Set progress bar type |
|
50 |
+ |
|
51 |
+ if (is.null(getOption("jags.pb"))) { |
|
52 |
+ options("jags.pb"="text") |
|
53 |
+ } |
|
54 |
+} |
0 | 55 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,163 @@ |
1 |
+# generated automatically by aclocal 1.10 -*- Autoconf -*- |
|
2 |
+ |
|
3 |
+# Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, |
|
4 |
+# 2005, 2006 Free Software Foundation, Inc. |
|
5 |
+# This file is free software; the Free Software Foundation |
|
6 |
+# gives unlimited permission to copy and/or distribute it, |
|
7 |
+# with or without modifications, as long as this notice is preserved. |
|
8 |
+ |
|
9 |
+# This program is distributed in the hope that it will be useful, |
|
10 |
+# but WITHOUT ANY WARRANTY, to the extent permitted by law; without |
|
11 |
+# even the implied warranty of MERCHANTABILITY or FITNESS FOR A |
|
12 |
+# PARTICULAR PURPOSE. |
|
13 |
+ |
|
14 |
+# pkg.m4 - Macros to locate and utilise pkg-config. -*- Autoconf -*- |
|
15 |
+# |
|
16 |
+# Copyright © 2004 Scott James Remnant <scott@netsplit.com>. |
|
17 |
+# |
|
18 |
+# This program is free software; you can redistribute it and/or modify |
|
19 |
+# it under the terms of the GNU General Public License as published by |
|
20 |
+# the Free Software Foundation; either version 2 of the License, or |
|
21 |
+# (at your option) any later version. |
|
22 |
+# |
|
23 |
+# This program is distributed in the hope that it will be useful, but |
|
24 |
+# WITHOUT ANY WARRANTY; without even the implied warranty of |
|
25 |
+# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
|
26 |
+# General Public License for more details. |
|
27 |
+# |
|
28 |
+# You should have received a copy of the GNU General Public License |
|
29 |
+# along with this program; if not, write to the Free Software |
|
30 |
+# Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. |
|
31 |
+# |
|
32 |
+# As a special exception to the GNU General Public License, if you |
|
33 |
+# distribute this file as part of a program that contains a |
|
34 |
+# configuration script generated by Autoconf, you may include it under |
|
35 |
+# the same distribution terms that you use for the rest of that program. |
|
36 |
+ |
|
37 |
+# PKG_PROG_PKG_CONFIG([MIN-VERSION]) |
|
38 |
+# ---------------------------------- |
|
39 |
+AC_DEFUN([PKG_PROG_PKG_CONFIG], |
|
40 |
+[m4_pattern_forbid([^_?PKG_[A-Z_]+$]) |
|
41 |
+m4_pattern_allow([^PKG_CONFIG(_PATH)?$]) |
|
42 |
+AC_ARG_VAR([PKG_CONFIG], [path to pkg-config utility])dnl |
|
43 |
+if test "x$ac_cv_env_PKG_CONFIG_set" != "xset"; then |
|
44 |
+ AC_PATH_TOOL([PKG_CONFIG], [pkg-config]) |
|
45 |
+fi |
|
46 |
+if test -n "$PKG_CONFIG"; then |
|
47 |
+ _pkg_min_version=m4_default([$1], [0.9.0]) |
|
48 |
+ AC_MSG_CHECKING([pkg-config is at least version $_pkg_min_version]) |
|
49 |
+ if $PKG_CONFIG --atleast-pkgconfig-version $_pkg_min_version; then |
|
50 |
+ AC_MSG_RESULT([yes]) |
|
51 |
+ else |
|
52 |
+ AC_MSG_RESULT([no]) |
|
53 |
+ PKG_CONFIG="" |
|
54 |
+ fi |
|
55 |
+ |
|
56 |
+fi[]dnl |
|
57 |
+])# PKG_PROG_PKG_CONFIG |
|
58 |
+ |
|
59 |
+# PKG_CHECK_EXISTS(MODULES, [ACTION-IF-FOUND], [ACTION-IF-NOT-FOUND]) |
|
60 |
+# |
|
61 |
+# Check to see whether a particular set of modules exists. Similar |
|
62 |
+# to PKG_CHECK_MODULES(), but does not set variables or print errors. |
|
63 |
+# |
|
64 |
+# |
|
65 |
+# Similar to PKG_CHECK_MODULES, make sure that the first instance of |
|
66 |
+# this or PKG_CHECK_MODULES is called, or make sure to call |
|
67 |
+# PKG_CHECK_EXISTS manually |
|
68 |
+# -------------------------------------------------------------- |
|
69 |
+AC_DEFUN([PKG_CHECK_EXISTS], |
|
70 |
+[AC_REQUIRE([PKG_PROG_PKG_CONFIG])dnl |
|
71 |
+if test -n "$PKG_CONFIG" && \ |
|
72 |
+ AC_RUN_LOG([$PKG_CONFIG --exists --print-errors "$1"]); then |
|
73 |
+ m4_ifval([$2], [$2], [:]) |
|
74 |
+m4_ifvaln([$3], [else |
|
75 |
+ $3])dnl |
|
76 |
+fi]) |
|
77 |
+ |
|
78 |
+ |
|
79 |
+# _PKG_CONFIG([VARIABLE], [COMMAND], [MODULES]) |
|
80 |
+# --------------------------------------------- |
|
81 |
+m4_define([_PKG_CONFIG], |
|
82 |
+[if test -n "$PKG_CONFIG"; then |
|
83 |
+ if test -n "$$1"; then |
|
84 |
+ pkg_cv_[]$1="$$1" |
|
85 |
+ else |
|
86 |
+ PKG_CHECK_EXISTS([$3], |
|
87 |
+ [pkg_cv_[]$1=`$PKG_CONFIG --[]$2 "$3" 2>/dev/null`], |
|
88 |
+ [pkg_failed=yes]) |
|
89 |
+ fi |
|
90 |
+else |
|
91 |
+ pkg_failed=untried |
|
92 |
+fi[]dnl |
|
93 |
+])# _PKG_CONFIG |
|
94 |
+ |
|
95 |
+# _PKG_SHORT_ERRORS_SUPPORTED |
|
96 |
+# ----------------------------- |
|
97 |
+AC_DEFUN([_PKG_SHORT_ERRORS_SUPPORTED], |
|
98 |
+[AC_REQUIRE([PKG_PROG_PKG_CONFIG]) |
|
99 |
+if $PKG_CONFIG --atleast-pkgconfig-version 0.20; then |
|
100 |
+ _pkg_short_errors_supported=yes |
|
101 |
+else |
|
102 |
+ _pkg_short_errors_supported=no |
|
103 |
+fi[]dnl |
|
104 |
+])# _PKG_SHORT_ERRORS_SUPPORTED |
|
105 |
+ |
|
106 |
+ |
|
107 |
+# PKG_CHECK_MODULES(VARIABLE-PREFIX, MODULES, [ACTION-IF-FOUND], |
|
108 |
+# [ACTION-IF-NOT-FOUND]) |
|
109 |
+# |
|
110 |
+# |
|
111 |
+# Note that if there is a possibility the first call to |
|
112 |
+# PKG_CHECK_MODULES might not happen, you should be sure to include an |
|
113 |
+# explicit call to PKG_PROG_PKG_CONFIG in your configure.ac |
|
114 |
+# |
|
115 |
+# |
|
116 |
+# -------------------------------------------------------------- |
|
117 |
+AC_DEFUN([PKG_CHECK_MODULES], |
|
118 |
+[AC_REQUIRE([PKG_PROG_PKG_CONFIG])dnl |
|
119 |
+AC_ARG_VAR([$1][_CFLAGS], [C compiler flags for $1, overriding pkg-config])dnl |
|
120 |
+AC_ARG_VAR([$1][_LIBS], [linker flags for $1, overriding pkg-config])dnl |
|
121 |
+ |
|
122 |
+pkg_failed=no |
|
123 |
+AC_MSG_CHECKING([for $1]) |
|
124 |
+ |
|
125 |
+_PKG_CONFIG([$1][_CFLAGS], [cflags], [$2]) |
|
126 |
+_PKG_CONFIG([$1][_LIBS], [libs], [$2]) |
|
127 |
+ |
|
128 |
+if test $pkg_failed = yes; then |
|
129 |
+ _PKG_SHORT_ERRORS_SUPPORTED |
|
130 |
+ if test $_pkg_short_errors_supported = yes; then |
|
131 |
+ $1[]_PKG_ERRORS=`$PKG_CONFIG --short-errors --errors-to-stdout --print-errors "$2"` |
|
132 |
+ else |
|
133 |
+ $1[]_PKG_ERRORS=`$PKG_CONFIG --errors-to-stdout --print-errors "$2"` |
|
134 |
+ fi |
|
135 |
+ # Put the nasty error message in config.log where it belongs |
|
136 |
+ echo "$$1[]_PKG_ERRORS" >&AS_MESSAGE_LOG_FD |
|
137 |
+ |
|
138 |
+ ifelse([$4], , [AC_MSG_ERROR(dnl |
|
139 |
+[Package requirements ($2) were not met: |
|
140 |
+ |
|
141 |
+$$1_PKG_ERRORS |
|
142 |
+ |
|
143 |
+Consider adjusting the PKG_CONFIG_PATH environment variable if you |
|
144 |
+installed software in a non-standard prefix. |
|
145 |
+])], |
|
146 |
+ [AC_MSG_RESULT([no]) |
|
147 |
+ $4]) |
|
148 |
+elif test $pkg_failed = untried; then |
|
149 |
+ ifelse([$4], , [AC_MSG_FAILURE(dnl |
|
150 |
+[The pkg-config script could not be found or is too old. Make sure it |
|
151 |
+is in your PATH or set the PKG_CONFIG environment variable to the full |
|
152 |
+path to pkg-config. |
|
153 |
+ |
|
154 |
+To get pkg-config, see <http://pkg-config.freedesktop.org/>.])], |
|
155 |
+ [$4]) |
|
156 |
+else |
|
157 |
+ $1[]_CFLAGS=$pkg_cv_[]$1[]_CFLAGS |
|
158 |
+ $1[]_LIBS=$pkg_cv_[]$1[]_LIBS |
|
159 |
+ AC_MSG_RESULT([yes]) |
|
160 |
+ ifelse([$3], , :, [$3]) |
|
161 |
+fi[]dnl |
|
162 |
+])# PKG_CHECK_MODULES |
|
163 |
+ |
0 | 4 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,408 @@ |
1 |
+This file contains any messages produced by compilers while |
|
2 |
+running configure, to aid debugging if configure makes a mistake. |
|
3 |
+ |
|
4 |
+It was created by CoGAPS configure 2.1.0, which was |
|
5 |
+generated by GNU Autoconf 2.63. Invocation command line was |
|
6 |
+ |
|
7 |
+ $ ./configure --with-jags-include=/usr/local/include/GAPS-JAGS --with-jags-lib=/usr/local/lib --with-jags-modules=/usr/local/lib/JAGS/modules-1.0.2 |
|
8 |
+ |
|
9 |
+## --------- ## |
|
10 |
+## Platform. ## |
|
11 |
+## --------- ## |
|
12 |
+ |
|
13 |
+hostname = Elana-Fertigs-Mac-Pro.local |
|
14 |
+uname -m = x86_64 |
|
15 |
+uname -r = 10.8.0 |
|
16 |
+uname -s = Darwin |
|
17 |
+uname -v = Darwin Kernel Version 10.8.0: Tue Jun 7 16:32:41 PDT 2011; root:xnu-1504.15.3~1/RELEASE_X86_64 |
|
18 |
+ |
|
19 |
+/usr/bin/uname -p = i386 |
|
20 |
+/bin/uname -X = unknown |
|
21 |
+ |
|
22 |
+/bin/arch = unknown |
|
23 |
+/usr/bin/arch -k = unknown |
|
24 |
+/usr/convex/getsysinfo = unknown |
|
25 |
+/usr/bin/hostinfo = Mach kernel version: |
|
26 |
+ Darwin Kernel Version 10.8.0: Tue Jun 7 16:32:41 PDT 2011; root:xnu-1504.15.3~1/RELEASE_X86_64 |
|
27 |
+Kernel configured for up to 8 processors. |
|
28 |
+4 processors are physically available. |
|
29 |
+8 processors are logically available. |
|
30 |
+Processor type: i486 (Intel 80486) |
|
31 |
+Processors active: 0 1 2 3 4 5 6 7 |
|
32 |
+Primary memory available: 16.00 gigabytes |
|
33 |
+Default processor set: 83 tasks, 317 threads, 8 processors |
|
34 |
+Load average: 2.67, Mach factor: 5.32 |
|
35 |
+/bin/machine = unknown |
|
36 |
+/usr/bin/oslevel = unknown |
|
37 |
+/bin/universe = unknown |
|
38 |
+ |
|
39 |
+PATH: /Users/ejfertig/Documents/SupportScripts |
|
40 |
+PATH: /opt/local/bin |
|
41 |
+PATH: /opt/local/sbin |
|
42 |
+PATH: /Users/ejfertig/Documents/SupportScripts |
|
43 |
+PATH: /opt/local/bin |
|
44 |
+PATH: /opt/local/sbin |
|
45 |
+PATH: /usr/bin |
|
46 |
+PATH: /bin |
|
47 |
+PATH: /usr/sbin |
|
48 |
+PATH: /sbin |
|
49 |
+PATH: /usr/local/bin |
|
50 |
+PATH: /usr/texbin |
|
51 |
+PATH: /usr/X11/bin |
|
52 |
+PATH: /Applications/MATLAB_R2010b.app/bin/ |
|
53 |
+PATH: /Applications/MATLAB_R2010b.app/bin/ |
|
54 |
+ |
|
55 |
+ |
|
56 |
+## ----------- ## |
|
57 |
+## Core tests. ## |
|
58 |
+## ----------- ## |
|
59 |
+ |
|
60 |
+configure:1803: checking for jags |
|
61 |
+configure:1821: found /usr/local/bin/jags |
|
62 |
+configure:1833: result: /usr/local/bin/jags |
|
63 |
+configure:1981: checking for g++ |
|
64 |
+configure:1997: found /usr/bin/g++ |
|
65 |
+configure:2008: result: g++ |
|
66 |
+configure:2035: checking for C++ compiler version |
|
67 |
+configure:2043: g++ --version >&5 |
|
68 |
+i686-apple-darwin10-g++-4.2.1 (GCC) 4.2.1 (Apple Inc. build 5666) (dot 3) |
|
69 |
+Copyright (C) 2007 Free Software Foundation, Inc. |
|
70 |
+This is free software; see the source for copying conditions. There is NO |
|
71 |
+warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. |
|
72 |
+ |
|
73 |
+configure:2047: $? = 0 |
|
74 |
+configure:2054: g++ -v >&5 |
|
75 |
+Using built-in specs. |
|
76 |
+Target: i686-apple-darwin10 |
|
77 |
+Configured with: /var/tmp/gcc/gcc-5666.3~6/src/configure --disable-checking --enable-werror --prefix=/usr --mandir=/share/man --enable-languages=c,objc,c++,obj-c++ --program-transform-name=/^[cg][^.-]*$/s/$/-4.2/ --with-slibdir=/usr/lib --build=i686-apple-darwin10 --program-prefix=i686-apple-darwin10- --host=x86_64-apple-darwin10 --target=i686-apple-darwin10 --with-gxx-include-dir=/include/c++/4.2.1 |
|
78 |
+Thread model: posix |
|
79 |
+gcc version 4.2.1 (Apple Inc. build 5666) (dot 3) |
|
80 |
+configure:2058: $? = 0 |
|
81 |
+configure:2065: g++ -V >&5 |
|
82 |
+g++-4.2: argument to `-V' is missing |
|
83 |
+configure:2069: $? = 1 |
|
84 |
+configure:2092: checking for C++ compiler default output file name |
|
85 |
+configure:2114: g++ -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
86 |
+configure:2118: $? = 0 |
|
87 |
+configure:2156: result: a.out |
|
88 |
+configure:2175: checking whether the C++ compiler works |
|
89 |
+configure:2185: ./a.out |
|
90 |
+configure:2189: $? = 0 |
|
91 |
+configure:2208: result: yes |
|
92 |
+configure:2215: checking whether we are cross compiling |
|
93 |
+configure:2217: result: no |
|
94 |
+configure:2220: checking for suffix of executables |
|
95 |
+configure:2227: g++ -o conftest -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
96 |
+configure:2231: $? = 0 |
|
97 |
+configure:2257: result: |
|
98 |
+configure:2263: checking for suffix of object files |
|
99 |
+configure:2289: g++ -c -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
100 |
+configure:2293: $? = 0 |
|
101 |
+configure:2318: result: o |
|
102 |
+configure:2322: checking whether we are using the GNU C++ compiler |
|
103 |
+configure:2351: g++ -c -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
104 |
+configure:2358: $? = 0 |
|
105 |
+configure:2375: result: yes |
|
106 |
+configure:2384: checking whether g++ accepts -g |
|
107 |
+configure:2414: g++ -c -g -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
108 |
+configure:2421: $? = 0 |
|
109 |
+configure:2522: result: yes |
|
110 |
+configure:2551: checking how to run the C++ preprocessor |
|
111 |
+configure:2587: g++ -E -I/usr/local/include/GAPS-JAGS conftest.cpp |
|
112 |
+configure:2594: $? = 0 |
|
113 |
+configure:2625: g++ -E -I/usr/local/include/GAPS-JAGS conftest.cpp |
|
114 |
+conftest.cpp:8:28: error: ac_nonexistent.h: No such file or directory |
|
115 |
+configure:2632: $? = 1 |
|
116 |
+configure: failed program was: |
|
117 |
+| /* confdefs.h. */ |
|
118 |
+| #define PACKAGE_NAME "CoGAPS" |
|
119 |
+| #define PACKAGE_TARNAME "CoGAPS" |
|
120 |
+| #define PACKAGE_VERSION "2.1.0" |
|
121 |
+| #define PACKAGE_STRING "CoGAPS 2.1.0" |
|
122 |
+| #define PACKAGE_BUGREPORT "" |
|
123 |
+| /* end confdefs.h. */ |
|
124 |
+| #include <ac_nonexistent.h> |
|
125 |
+configure:2665: result: g++ -E |
|
126 |
+configure:2694: g++ -E -I/usr/local/include/GAPS-JAGS conftest.cpp |
|
127 |
+configure:2701: $? = 0 |
|
128 |
+configure:2732: g++ -E -I/usr/local/include/GAPS-JAGS conftest.cpp |
|
129 |
+conftest.cpp:8:28: error: ac_nonexistent.h: No such file or directory |
|
130 |
+configure:2739: $? = 1 |
|
131 |
+configure: failed program was: |
|
132 |
+| /* confdefs.h. */ |
|
133 |
+| #define PACKAGE_NAME "CoGAPS" |
|
134 |
+| #define PACKAGE_TARNAME "CoGAPS" |
|
135 |
+| #define PACKAGE_VERSION "2.1.0" |
|
136 |
+| #define PACKAGE_STRING "CoGAPS 2.1.0" |
|
137 |
+| #define PACKAGE_BUGREPORT "" |
|
138 |
+| /* end confdefs.h. */ |
|
139 |
+| #include <ac_nonexistent.h> |
|
140 |
+configure:2779: checking for grep that handles long lines and -e |
|
141 |
+configure:2839: result: /usr/bin/grep |
|
142 |
+configure:2844: checking for egrep |
|
143 |
+configure:2908: result: /usr/bin/grep -E |
|
144 |
+configure:2913: checking for ANSI C header files |
|
145 |
+configure:2943: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
146 |
+configure:2950: $? = 0 |
|
147 |
+configure:3049: g++ -o conftest -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
148 |
+configure:3053: $? = 0 |
|
149 |
+configure:3059: ./conftest |
|
150 |
+configure:3063: $? = 0 |
|
151 |
+configure:3081: result: yes |
|
152 |
+configure:3105: checking for sys/types.h |
|
153 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
154 |
+configure:3133: $? = 0 |
|
155 |
+configure:3150: result: yes |
|
156 |
+configure:3105: checking for sys/stat.h |
|
157 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
158 |
+configure:3133: $? = 0 |
|
159 |
+configure:3150: result: yes |
|
160 |
+configure:3105: checking for stdlib.h |
|
161 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
162 |
+configure:3133: $? = 0 |
|
163 |
+configure:3150: result: yes |
|
164 |
+configure:3105: checking for string.h |
|
165 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
166 |
+configure:3133: $? = 0 |
|
167 |
+configure:3150: result: yes |
|
168 |
+configure:3105: checking for memory.h |
|
169 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
170 |
+configure:3133: $? = 0 |
|
171 |
+configure:3150: result: yes |
|
172 |
+configure:3105: checking for strings.h |
|
173 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
174 |
+configure:3133: $? = 0 |
|
175 |
+configure:3150: result: yes |
|
176 |
+configure:3105: checking for inttypes.h |
|
177 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
178 |
+configure:3133: $? = 0 |
|
179 |
+configure:3150: result: yes |
|
180 |
+configure:3105: checking for stdint.h |
|
181 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
182 |
+configure:3133: $? = 0 |
|
183 |
+configure:3150: result: yes |
|
184 |
+configure:3105: checking for unistd.h |
|
185 |
+configure:3126: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
186 |
+configure:3133: $? = 0 |
|
187 |
+configure:3150: result: yes |
|
188 |
+configure:3174: checking Console.h usability |
|
189 |
+configure:3191: g++ -c -g -O2 -I/usr/local/include/GAPS-JAGS conftest.cpp >&5 |
|
190 |
+configure:3198: $? = 0 |
|
191 |
+configure:3212: result: yes |
|
192 |
+configure:3216: checking Console.h presence |
|
193 |
+configure:3231: g++ -E -I/usr/local/include/GAPS-JAGS conftest.cpp |
|
194 |
+configure:3238: $? = 0 |
|
195 |
+configure:3252: result: yes |
|
196 |
+configure:3280: checking for Console.h |
|
197 |
+configure:3287: result: yes |
|
198 |
+configure:3411: checking for gcc |
|
199 |
+configure:3427: found /usr/bin/gcc |
|
200 |
+configure:3438: result: gcc |
|
201 |
+configure:3670: checking for C compiler version |
|
202 |
+configure:3678: gcc --version >&5 |
|
203 |
+i686-apple-darwin10-gcc-4.2.1 (GCC) 4.2.1 (Apple Inc. build 5666) (dot 3) |
|
204 |
+Copyright (C) 2007 Free Software Foundation, Inc. |
|
205 |
+This is free software; see the source for copying conditions. There is NO |
|
206 |
+warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. |
|
207 |
+ |
|
208 |
+configure:3682: $? = 0 |
|
209 |
+configure:3689: gcc -v >&5 |
|
210 |
+Using built-in specs. |
|
211 |
+Target: i686-apple-darwin10 |
|
212 |
+Configured with: /var/tmp/gcc/gcc-5666.3~6/src/configure --disable-checking --enable-werror --prefix=/usr --mandir=/share/man --enable-languages=c,objc,c++,obj-c++ --program-transform-name=/^[cg][^.-]*$/s/$/-4.2/ --with-slibdir=/usr/lib --build=i686-apple-darwin10 --program-prefix=i686-apple-darwin10- --host=x86_64-apple-darwin10 --target=i686-apple-darwin10 --with-gxx-include-dir=/include/c++/4.2.1 |
|
213 |
+Thread model: posix |
|
214 |
+gcc version 4.2.1 (Apple Inc. build 5666) (dot 3) |
|
215 |
+configure:3693: $? = 0 |
|
216 |
+configure:3700: gcc -V >&5 |
|
217 |
+gcc-4.2: argument to `-V' is missing |
|
218 |
+configure:3704: $? = 1 |
|
219 |
+configure:3707: checking whether we are using the GNU C compiler |
|
220 |
+configure:3736: gcc -c conftest.c >&5 |
|
221 |
+configure:3743: $? = 0 |
|
222 |
+configure:3760: result: yes |
|
223 |
+configure:3769: checking whether gcc accepts -g |
|
224 |
+configure:3799: gcc -c -g conftest.c >&5 |
|
225 |
+configure:3806: $? = 0 |
|
226 |
+configure:3907: result: yes |
|
227 |
+configure:3924: checking for gcc option to accept ISO C89 |
|
228 |
+configure:3998: gcc -c -g -O2 conftest.c >&5 |
|
229 |
+configure:4005: $? = 0 |
|
230 |
+configure:4028: result: none needed |
|
231 |
+configure:4048: checking for jags_version in -ljags |
|
232 |
+configure:4083: gcc -o conftest -g -O2 -L/usr/local/lib conftest.c -ljags >&5 |
|
233 |
+configure:4090: $? = 0 |
|
234 |
+configure:4111: result: yes |
|
235 |
+configure:4301: creating ./config.status |
|
236 |
+ |
|
237 |
+## ---------------------- ## |
|
238 |
+## Running config.status. ## |
|
239 |
+## ---------------------- ## |
|
240 |
+ |
|
241 |
+This file was extended by CoGAPS config.status 2.1.0, which was |
|
242 |
+generated by GNU Autoconf 2.63. Invocation command line was |
|
243 |
+ |
|
244 |
+ CONFIG_FILES = |
|
245 |
+ CONFIG_HEADERS = |
|
246 |
+ CONFIG_LINKS = |
|
247 |
+ CONFIG_COMMANDS = |
|
248 |
+ $ ./config.status |
|
249 |
+ |
|
250 |
+on Elana-Fertigs-Mac-Pro.local |
|
251 |
+ |
|
252 |
+config.status:652: creating src/Makevars |
|
253 |
+configure:5413: creating ./config.status |
|
254 |
+ |
|
255 |
+## ---------------------- ## |
|
256 |
+## Running config.status. ## |
|
257 |
+## ---------------------- ## |
|
258 |
+ |
|
259 |
+This file was extended by CoGAPS config.status 2.1.0, which was |
|
260 |
+generated by GNU Autoconf 2.63. Invocation command line was |
|
261 |
+ |
|
262 |
+ CONFIG_FILES = |
|
263 |
+ CONFIG_HEADERS = |
|
264 |
+ CONFIG_LINKS = |
|
265 |
+ CONFIG_COMMANDS = |
|
266 |
+ $ ./config.status |
|
267 |
+ |
|
268 |
+on Elana-Fertigs-Mac-Pro.local |
|
269 |
+ |
|
270 |
+config.status:653: creating src/Makevars |
|
271 |
+config.status:653: creating R/unix/zzz.R |
|
272 |
+ |
|
273 |
+## ---------------- ## |
|
274 |
+## Cache variables. ## |
|
275 |
+## ---------------- ## |
|
276 |
+ |
|
277 |
+ac_cv_c_compiler_gnu=yes |
|
278 |
+ac_cv_cxx_compiler_gnu=yes |
|
279 |
+ac_cv_env_CCC_set= |
|
280 |
+ac_cv_env_CCC_value= |
|
281 |
+ac_cv_env_CC_set= |
|
282 |
+ac_cv_env_CC_value= |
|
283 |
+ac_cv_env_CFLAGS_set= |
|
284 |
+ac_cv_env_CFLAGS_value= |
|
285 |
+ac_cv_env_CPPFLAGS_set= |
|
286 |
+ac_cv_env_CPPFLAGS_value= |
|
287 |
+ac_cv_env_CXXCPP_set= |
|
288 |
+ac_cv_env_CXXCPP_value= |
|
289 |
+ac_cv_env_CXXFLAGS_set= |
|
290 |
+ac_cv_env_CXXFLAGS_value= |
|
291 |
+ac_cv_env_CXX_set= |
|
292 |
+ac_cv_env_CXX_value= |
|
293 |
+ac_cv_env_LDFLAGS_set= |
|
294 |
+ac_cv_env_LDFLAGS_value= |
|
295 |
+ac_cv_env_LIBS_set= |
|
296 |
+ac_cv_env_LIBS_value= |
|
297 |
+ac_cv_env_build_alias_set= |
|
298 |
+ac_cv_env_build_alias_value= |
|
299 |
+ac_cv_env_host_alias_set= |
|
300 |
+ac_cv_env_host_alias_value= |
|
301 |
+ac_cv_env_target_alias_set= |
|
302 |
+ac_cv_env_target_alias_value= |
|
303 |
+ac_cv_header_Console_h=yes |
|
304 |
+ac_cv_header_inttypes_h=yes |
|
305 |
+ac_cv_header_memory_h=yes |
|
306 |
+ac_cv_header_stdc=yes |
|
307 |
+ac_cv_header_stdint_h=yes |
|
308 |
+ac_cv_header_stdlib_h=yes |
|
309 |
+ac_cv_header_string_h=yes |
|
310 |
+ac_cv_header_strings_h=yes |
|
311 |
+ac_cv_header_sys_stat_h=yes |
|
312 |
+ac_cv_header_sys_types_h=yes |
|
313 |
+ac_cv_header_unistd_h=yes |
|
314 |
+ac_cv_lib_jags_jags_version=yes |
|
315 |
+ac_cv_objext=o |
|
316 |
+ac_cv_path_EGREP='/usr/bin/grep -E' |
|
317 |
+ac_cv_path_GREP=/usr/bin/grep |
|
318 |
+ac_cv_path_ac_prefix_program=/usr/local/bin/jags |
|
319 |
+ac_cv_prog_CXXCPP='g++ -E' |
|
320 |
+ac_cv_prog_ac_ct_CC=gcc |
|
321 |
+ac_cv_prog_ac_ct_CXX=g++ |
|
322 |
+ac_cv_prog_cc_c89= |
|
323 |
+ac_cv_prog_cc_g=yes |
|
324 |
+ac_cv_prog_cxx_g=yes |
|
325 |
+ |
|
326 |
+## ----------------- ## |
|
327 |
+## Output variables. ## |
|
328 |
+## ----------------- ## |
|
329 |
+ |
|
330 |
+CC='gcc' |
|
331 |
+CFLAGS='-g -O2' |
|
332 |
+CPPFLAGS='' |
|
333 |
+CXX='g++' |
|
334 |
+CXXCPP='g++ -E' |
|
335 |
+CXXFLAGS='-g -O2' |
|
336 |
+DEFS='-DPACKAGE_NAME=\"CoGAPS\" -DPACKAGE_TARNAME=\"CoGAPS\" -DPACKAGE_VERSION=\"2.1.0\" -DPACKAGE_STRING=\"CoGAPS\ 2.1.0\" -DPACKAGE_BUGREPORT=\"\" -DSTDC_HEADERS=1 -DHAVE_SYS_TYPES_H=1 -DHAVE_SYS_STAT_H=1 -DHAVE_STDLIB_H=1 -DHAVE_STRING_H=1 -DHAVE_MEMORY_H=1 -DHAVE_STRINGS_H=1 -DHAVE_INTTYPES_H=1 -DHAVE_STDINT_H=1 -DHAVE_UNISTD_H=1 -DHAVE_LIBJAGS=1' |
|
337 |
+ECHO_C='\c' |
|
338 |
+ECHO_N='' |
|
339 |
+ECHO_T='' |
|
340 |
+EGREP='/usr/bin/grep -E' |
|
341 |
+EXEEXT='' |
|
342 |
+GREP='/usr/bin/grep' |
|
343 |
+JAGS_INCLUDE='/usr/local/include/GAPS-JAGS' |
|
344 |
+JAGS_LIB='/usr/local/lib' |
|
345 |
+JAGS_MODULES='/usr/local/lib/JAGS/modules-1.0.2' |
|
346 |
+LDFLAGS='' |
|
347 |
+LIBOBJS='' |
|
348 |
+LIBS='-ljags ' |
|
349 |
+LTLIBOBJS='' |
|
350 |
+OBJEXT='o' |
|
351 |
+PACKAGE_BUGREPORT='' |
|
352 |
+PACKAGE_NAME='CoGAPS' |
|
353 |
+PACKAGE_STRING='CoGAPS 2.1.0' |
|
354 |
+PACKAGE_TARNAME='CoGAPS' |
|
355 |
+PACKAGE_VERSION='2.1.0' |
|
356 |
+PATH_SEPARATOR=':' |
|
357 |
+SHELL='/bin/sh' |
|
358 |
+ac_ct_CC='gcc' |
|
359 |
+ac_ct_CXX='g++' |
|
360 |
+ac_prefix_program='/usr/local/bin/jags' |
|
361 |
+bindir='${exec_prefix}/bin' |
|
362 |
+build_alias='' |
|
363 |
+datadir='${datarootdir}' |
|
364 |
+datarootdir='${prefix}/share' |
|
365 |
+docdir='${datarootdir}/doc/${PACKAGE_TARNAME}' |
|
366 |
+dvidir='${docdir}' |
|
367 |
+exec_prefix='${prefix}' |
|
368 |
+host_alias='' |
|
369 |
+htmldir='${docdir}' |
|
370 |
+includedir='${prefix}/include' |
|
371 |
+infodir='${datarootdir}/info' |
|
372 |
+libdir='${exec_prefix}/lib' |
|
373 |
+libexecdir='${exec_prefix}/libexec' |
|
374 |
+localedir='${datarootdir}/locale' |
|
375 |
+localstatedir='${prefix}/var' |
|
376 |
+mandir='${datarootdir}/man' |
|
377 |
+oldincludedir='/usr/include' |
|
378 |
+pdfdir='${docdir}' |
|
379 |
+prefix='/usr/local' |
|
380 |
+program_transform_name='s,x,x,' |
|
381 |
+psdir='${docdir}' |
|
382 |
+sbindir='${exec_prefix}/sbin' |
|
383 |
+sharedstatedir='${prefix}/com' |
|
384 |
+sysconfdir='${prefix}/etc' |
|
385 |
+target_alias='' |
|
386 |
+ |
|
387 |
+## ----------- ## |
|
388 |
+## confdefs.h. ## |
|
389 |
+## ----------- ## |
|
390 |
+ |
|
391 |
+#define PACKAGE_NAME "CoGAPS" |
|
392 |
+#define PACKAGE_TARNAME "CoGAPS" |
|
393 |
+#define PACKAGE_VERSION "2.1.0" |
|
394 |
+#define PACKAGE_STRING "CoGAPS 2.1.0" |
|
395 |
+#define PACKAGE_BUGREPORT "" |
|
396 |
+#define STDC_HEADERS 1 |
|
397 |
+#define HAVE_SYS_TYPES_H 1 |
|
398 |
+#define HAVE_SYS_STAT_H 1 |
|
399 |
+#define HAVE_STDLIB_H 1 |
|
400 |
+#define HAVE_STRING_H 1 |
|
401 |
+#define HAVE_MEMORY_H 1 |
|
402 |
+#define HAVE_STRINGS_H 1 |
|
403 |
+#define HAVE_INTTYPES_H 1 |
|
404 |
+#define HAVE_STDINT_H 1 |
|
405 |
+#define HAVE_UNISTD_H 1 |
|
406 |
+#define HAVE_LIBJAGS 1 |
|
407 |
+ |
|
408 |
+configure: exit 0 |
0 | 409 |
new file mode 100755 |
... | ... |
@@ -0,0 +1,859 @@ |
1 |
+#! /bin/sh |
|
2 |
+# Generated by configure. |
|
3 |
+# Run this file to recreate the current configuration. |
|
4 |
+# Compiler output produced by configure, useful for debugging |
|
5 |
+# configure, is in config.log if it exists. |
|
6 |
+ |
|
7 |
+debug=false |
|
8 |
+ac_cs_recheck=false |
|
9 |
+ac_cs_silent=false |
|
10 |
+SHELL=${CONFIG_SHELL-/bin/sh} |
|
11 |
+## --------------------- ## |
|
12 |
+## M4sh Initialization. ## |
|
13 |
+## --------------------- ## |
|
14 |
+ |
|
15 |
+# Be more Bourne compatible |
|
16 |
+DUALCASE=1; export DUALCASE # for MKS sh |
|
17 |
+if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then |
|
18 |
+ emulate sh |
|
19 |
+ NULLCMD=: |
|
20 |
+ # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which |
|
21 |
+ # is contrary to our usage. Disable this feature. |
|
22 |
+ alias -g '${1+"$@"}'='"$@"' |
|
23 |
+ setopt NO_GLOB_SUBST |
|
24 |
+else |
|
25 |
+ case `(set -o) 2>/dev/null` in |
|
26 |
+ *posix*) set -o posix ;; |
|
27 |
+esac |
|
28 |
+ |
|
29 |
+fi |
|
30 |
+ |
|
31 |
+ |
|
32 |
+ |
|
33 |
+ |
|
34 |
+# PATH needs CR |
|
35 |
+# Avoid depending upon Character Ranges. |
|
36 |
+as_cr_letters='abcdefghijklmnopqrstuvwxyz' |
|
37 |
+as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' |
|
38 |
+as_cr_Letters=$as_cr_letters$as_cr_LETTERS |
|
39 |
+as_cr_digits='0123456789' |
|
40 |
+as_cr_alnum=$as_cr_Letters$as_cr_digits |
|
41 |
+ |
|
42 |
+as_nl=' |
|
43 |
+' |
|
44 |
+export as_nl |
|
45 |
+# Printing a long string crashes Solaris 7 /usr/bin/printf. |
|
46 |
+as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' |
|
47 |
+as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo |
|
48 |
+as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo |
|
49 |
+if (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then |
|
50 |
+ as_echo='printf %s\n' |
|
51 |
+ as_echo_n='printf %s' |
|
52 |
+else |
|
53 |
+ if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then |
|
54 |
+ as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' |
|
55 |
+ as_echo_n='/usr/ucb/echo -n' |
|
56 |
+ else |
|
57 |
+ as_echo_body='eval expr "X$1" : "X\\(.*\\)"' |
|
58 |
+ as_echo_n_body='eval |
|
59 |
+ arg=$1; |
|
60 |
+ case $arg in |
|
61 |
+ *"$as_nl"*) |
|
62 |
+ expr "X$arg" : "X\\(.*\\)$as_nl"; |
|
63 |
+ arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; |
|
64 |
+ esac; |
|
65 |
+ expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" |
|
66 |
+ ' |
|
67 |
+ export as_echo_n_body |
|
68 |
+ as_echo_n='sh -c $as_echo_n_body as_echo' |
|
69 |
+ fi |
|
70 |
+ export as_echo_body |
|
71 |
+ as_echo='sh -c $as_echo_body as_echo' |
|
72 |
+fi |
|
73 |
+ |
|
74 |
+# The user is always right. |
|
75 |
+if test "${PATH_SEPARATOR+set}" != set; then |
|
76 |
+ PATH_SEPARATOR=: |
|
77 |
+ (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { |
|
78 |
+ (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || |
|
79 |
+ PATH_SEPARATOR=';' |
|
80 |
+ } |
|
81 |
+fi |
|
82 |
+ |
|
83 |
+# Support unset when possible. |
|
84 |
+if ( (MAIL=60; unset MAIL) || exit) >/dev/null 2>&1; then |
|
85 |
+ as_unset=unset |
|
86 |
+else |
|
87 |
+ as_unset=false |
|
88 |
+fi |
|
89 |
+ |
|
90 |
+ |
|
91 |
+# IFS |
|
92 |
+# We need space, tab and new line, in precisely that order. Quoting is |
|
93 |
+# there to prevent editors from complaining about space-tab. |
|
94 |
+# (If _AS_PATH_WALK were called with IFS unset, it would disable word |
|
95 |
+# splitting by setting IFS to empty value.) |
|
96 |
+IFS=" "" $as_nl" |
|
97 |
+ |
|
98 |
+# Find who we are. Look in the path if we contain no directory separator. |
|
99 |
+case $0 in |
|
100 |
+ *[\\/]* ) as_myself=$0 ;; |
|
101 |
+ *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR |
|
102 |
+for as_dir in $PATH |
|
103 |
+do |
|
104 |
+ IFS=$as_save_IFS |
|
105 |
+ test -z "$as_dir" && as_dir=. |
|
106 |
+ test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break |
|
107 |
+done |
|
108 |
+IFS=$as_save_IFS |
|
109 |
+ |
|
110 |
+ ;; |
|
111 |
+esac |
|
112 |
+# We did not find ourselves, most probably we were run as `sh COMMAND' |
|
113 |
+# in which case we are not to be found in the path. |
|
114 |
+if test "x$as_myself" = x; then |
|
115 |
+ as_myself=$0 |
|
116 |
+fi |
|
117 |
+if test ! -f "$as_myself"; then |
|
118 |
+ $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 |
|
119 |
+ { (exit 1); exit 1; } |
|
120 |
+fi |
|
121 |
+ |
|
122 |
+# Work around bugs in pre-3.0 UWIN ksh. |
|
123 |
+for as_var in ENV MAIL MAILPATH |
|
124 |
+do ($as_unset $as_var) >/dev/null 2>&1 && $as_unset $as_var |
|
125 |
+done |
|
126 |
+PS1='$ ' |
|
127 |
+PS2='> ' |
|
128 |
+PS4='+ ' |
|
129 |
+ |
|
130 |
+# NLS nuisances. |
|
131 |
+LC_ALL=C |
|
132 |
+export LC_ALL |
|
133 |
+LANGUAGE=C |
|
134 |
+export LANGUAGE |
|
135 |
+ |
|
136 |
+# Required to use basename. |
|
137 |
+if expr a : '\(a\)' >/dev/null 2>&1 && |
|
138 |
+ test "X`expr 00001 : '.*\(...\)'`" = X001; then |
|
139 |
+ as_expr=expr |
|
140 |
+else |
|
141 |
+ as_expr=false |
|
142 |
+fi |
|
143 |
+ |
|
144 |
+if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then |
|
145 |
+ as_basename=basename |
|
146 |
+else |
|
147 |
+ as_basename=false |
|
148 |
+fi |
|
149 |
+ |
|
150 |
+ |
|
151 |
+# Name of the executable. |