From: <chr...@us...> - 2010-08-07 19:37:18
|
Revision: 164 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=164&view=rev Author: chris-jackson Date: 2010-08-07 19:37:04 +0000 (Sat, 07 Aug 2010) Log Message: ----------- New branch of BRugs with Linux support. Detailed description of changes in NEWS. Modified Paths: -------------- branches/linux/BRugs/DESCRIPTION branches/linux/BRugs/NAMESPACE branches/linux/BRugs/NEWS branches/linux/BRugs/R/bgr.point.R branches/linux/BRugs/R/dimensions.R branches/linux/BRugs/R/get.chain.R branches/linux/BRugs/R/info.node.R branches/linux/BRugs/R/internal.R branches/linux/BRugs/R/model.check.R branches/linux/BRugs/R/model.compile.R branches/linux/BRugs/R/model.inits.R branches/linux/BRugs/R/model.names.R branches/linux/BRugs/R/model.precision.R branches/linux/BRugs/R/model.setRN.R branches/linux/BRugs/R/plot.bgr.R branches/linux/BRugs/R/samples.coda.R branches/linux/BRugs/R/samples.correl.R branches/linux/BRugs/R/samples.get.beg.R branches/linux/BRugs/R/samples.get.end.R branches/linux/BRugs/R/samples.get.firstChain.R branches/linux/BRugs/R/samples.get.lastChain.R branches/linux/BRugs/R/samples.get.thin.R branches/linux/BRugs/R/samples.monitors.R branches/linux/BRugs/R/samples.sample.R branches/linux/BRugs/R/samples.set.beg.R branches/linux/BRugs/R/samples.set.end.R branches/linux/BRugs/R/samples.set.firstChain.R branches/linux/BRugs/R/samples.set.lastChain.R branches/linux/BRugs/R/samples.set.thin.R branches/linux/BRugs/R/samples.size.R branches/linux/BRugs/R/samples.stats.R branches/linux/BRugs/R/set.values.R branches/linux/BRugs/R/zzz.R branches/linux/BRugs/man/BRugs.Rd branches/linux/BRugs/man/BRugsFit.Rd branches/linux/BRugs/man/bgr.point.Rd branches/linux/BRugs/man/model.RN.Rd branches/linux/BRugs/man/set.values.Rd branches/linux/BRugs/src/Makevars branches/linux/BRugs/tests/BRugs.R branches/linux/BRugs/tests/examples.R branches/linux/BRugs/tests/functions.R Added Paths: ----------- branches/linux/BRugs/R/internal-linux.R branches/linux/BRugs/R/internal-win.R branches/linux/BRugs/exec/ branches/linux/BRugs/src/BugsHelper.c Removed Paths: ------------- branches/linux/BRugs/R/model.getRN.R branches/linux/BRugs/configure branches/linux/BRugs/configure.win Modified: branches/linux/BRugs/DESCRIPTION =================================================================== --- branches/linux/BRugs/DESCRIPTION 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/DESCRIPTION 2010-08-07 19:37:04 UTC (rev 164) @@ -2,11 +2,10 @@ Title: OpenBUGS and its R / S-PLUS interface BRugs Version: 0.6-0 Date: 2010-04-30 -Author: The Chief Software Bug is Andrew Thomas, with web assistance from Real Bug Bob O'Hara. Other members of the BUGS team are statisticians David Spiegelhalter, Nicky Best, Dave Lunn and Ken Rice. Dave Lunn has also made major contributions to the software development. R Code modified, extended and packaged for R by Uwe Ligges and Sibylle Sturtz. Some ideas taken from the R2WinBUGS package based on code by Andrew Gelman. With considerable contributions by Gregor Gorjanc <gre...@bf...>. +Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R Code modified, extended and packaged for R by Uwe Ligges and Sibylle Sturtz. Some ideas taken from the R2WinBUGS package based on code by Andrew Gelman. With considerable contributions by Gregor Gorjanc. Linux port of BRugs and other developments by Chris Jackson. Description: An R / S-PLUS package containing OpenBUGS and its R / S-PLUS interface BRugs. Maintainer: Uwe Ligges <li...@st...> Depends: R (>= 2.5.0), coda Archs: i386 -OS_type: windows License: GPL-2 URL: http://www.openbugs.info/ Modified: branches/linux/BRugs/NAMESPACE =================================================================== --- branches/linux/BRugs/NAMESPACE 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/NAMESPACE 2010-08-07 19:37:04 UTC (rev 164) @@ -1,4 +1,3 @@ -useDynLib(BRugs) importFrom(coda, mcmc, mcmc.list) export(BRugsFit, bugsData, bugsInits, buildMCMC, dicClear, dicSet, dicStats, @@ -6,7 +5,7 @@ infoMemory,infoModules,infoNodeValues,infoNodeMethods,infoNodeTypes, infoUpdatersbyName,infoUpdatersbyDepth, modelAdaptivePhase, modelCheck, modelCompile, modelData, -modelGenInits, modelGetRN, modelInits, modelIteration, +modelGenInits, modelInits, modelIteration, modelNames, modelPrecision, modelSaveState, modelSetAP, modelSetIts, modelSetOR, modelSetRN, modelUpdate, modelEnable, modelDisable, Modified: branches/linux/BRugs/NEWS =================================================================== --- branches/linux/BRugs/NEWS 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/NEWS 2010-08-07 19:37:04 UTC (rev 164) @@ -1,17 +1,75 @@ -Changes to BRugs: -===================== +CHANGES MADE FOR LINUX PORT OF BRugs -Update 0.6-0 -- Switch to new OpenBUGS (currently 3.1.0) -- 32-bit versions only +* A C program called BugsHelper is used to call the OpenBUGS shared + library on Linux via a system() call. With one call of BugsHelper, + any number of different OpenBUGS API commands can be run. The state + of the model is "internalized" on entry from a file in the temporary + directory, and "externalized" on exit. The source is in src/ and + the binary is installed into exec/. -Update 0.5-3 -- fix writeModel() again by going through parse tree now -- fix buildMCMC() to report right thinning parameters and keep all samples +* New function .OpenBUGS() to execute a sequence of OpenBUGS API + commands of possibly differing types (e.g. CmdInterpreter, + RealArray, Integer) with given arguments. On Windows, this is a + wrapper for the old method of calling C functions from the + dyn.load()-ed library. On Linux, this calls BugsHelper once. The + old .CmdInterpreter and related functions still have the same + interfaces, but work by calling .OpenBUGS(). +* Input and output from the OpenBUGS API on Linux is performed through + files input1.txt, output1.txt, input2.txt, output2.txt, ... in the + same /tmp/R*** directory as the buffer.txt file. The buffer.txt + file is used as before for messages from OpenBUGS. -Update 0.5-2 -- added seed argument to BRugsFit() -- fix writeModel() to work for separatly specified function body -- fix writeModel() to make larger numeric (particularly integer) values - in scientific notation work +* A set of global variables is stored in the options() list containing + the begin and end iterations, first and last chains, thin interval + and precision to calculate sample statistics. This is required + because the OpenBUGS Internalize / Externalize facility used by + BugsHelper does not save these variables, which are normally stored + in the OpenBUGS internal module SamplesEmbed. They are not saved + because OpenBUGS considers them to be part of the GUI state + (equivalent to the values typed in Inference->Samples...) rather + than the model state. These variables are reset when a new model is + checked and compiled. + +* As a result, all functions which compute sample statistics must + first call an API command which is returned by + .SamplesGlobalsCmd(node). This command updates the values stored in + SamplesEmbed using the values stored in options(). This ensures + that OpenBUGS knows about them before calculating sample statistics. + (Note this is still done on Windows where it is not necessary, but + there should be negligible overhead). The directly affected + functions are samplesCoda(), samplesSize(), samplesSample(), + samplesStats(), samplesCorrel(), plotBgr(). + +* .onLoad() in zzz.R initialises these global variables on Linux and + Windows. + +* The corresponding set/get functions are changed to read and write + these global variables instead of updating the values in + SamplesEmbed. + +* plotBGR() modified to use a single .OpenBUGS() call to return a list + of samples for each required iteration on the grid. bgrPoint() + takes a sample instead of a node and iteration. Using one + .OpenBUGS() call for each sample would be an order of magnitude + slower using the Linux helper program. Assume the extra memory + overhead, compared to the old method, is not a problem on Windows. + +* infoNodeValues() and SetValues() now read and write the values from + multiple chains, and work on scalars as well as vectors. + +* modelNames() modified to use a single .OpenBUGS call instead of + looping API commands over names in the model. + +* useDynLib(BRugs) removed from NAMESPACE. This is done in .OnLoad() + instead, to ensure that it is only used on Windows. + +* modelGetRN() removed, as the initial random number preset is not + saved by the Externalize facility. The random number state however + is saved and restored properly during the model run. There is no + need for the initial preset to be read by the user, as it does not + change as the model runs. + +* samplesCorrel() wasn't setting begin/end/thin etc. properly, since + the CorrelEmbed module doesn't use the values in SamplesEmbed. + These are now read from the variables in options(). Modified: branches/linux/BRugs/R/bgr.point.R =================================================================== --- branches/linux/BRugs/R/bgr.point.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/bgr.point.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,14 +1,9 @@ "bgrPoint" <- -function(node, iteration) -# Calculate the bgr statistic at iteration +function(sample) +# Calculate the bgr statistic given a sample concatenated over chains { - oldEnd <- samplesGetEnd() - on.exit(samplesSetEnd(oldEnd)) - samplesSetEnd(as.integer(iteration)) numChains <- getNumChains() - sampleSize <- samplesSize(node) - command <- "SamplesEmbed.SampleValues" - sample <- samplesSample(node) + sampleSize <- length(sample) lenChain <- sampleSize %/% numChains if (is.R()) dq <- quantile(sample, c(0.1, 0.9), names = FALSE) @@ -25,5 +20,5 @@ } n.delta <- n.delta / numChains bgr.stat <- d.delta / n.delta - return(c(iteration, n.delta, d.delta, bgr.stat)) + return(c(n.delta, d.delta, bgr.stat)) } Modified: branches/linux/BRugs/R/dimensions.R =================================================================== --- branches/linux/BRugs/R/dimensions.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/dimensions.R 2010-08-07 19:37:04 UTC (rev 164) @@ -5,9 +5,8 @@ nodeLabel <- as.character(node) if(!(nodeLabel %in% modelNames())) stop("node must be a variable name from the model") - command <- "BugsRobjects.SetVariable" - .C("CharArray", command, nchar(command), nodeLabel, nchar(nodeLabel), integer(1), PACKAGE="BRugs") - command <- "BugsRobjects.GetNumDimensions" - dimensions <- .Integer(command) - return(dimensions) + dimensions <- .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.GetNumDimensions"), + c("CharArray", "Integer"), + list(nodeLabel, NA))[[2]] + dimensions } Modified: branches/linux/BRugs/R/get.chain.R =================================================================== --- branches/linux/BRugs/R/get.chain.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/get.chain.R 2010-08-07 19:37:04 UTC (rev 164) @@ -2,6 +2,5 @@ function() # Get chain field { - command<- "BugsEmbed.chain" - .Integer(command) + getOption("BRugsNextChain") } Modified: branches/linux/BRugs/R/info.node.R =================================================================== --- branches/linux/BRugs/R/info.node.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/info.node.R 2010-08-07 19:37:04 UTC (rev 164) @@ -3,16 +3,18 @@ # Get current value of node { nodeLabel <- as.character(nodeLabel) - command <- "BugsRobjects.SetVariable" - len <- nchar(command) - .C("CharArray", command, as.integer(len), nodeLabel, nchar(nodeLabel), integer(1), PACKAGE="BRugs") - command <- "BugsRobjects.GetSize" - nodeSize <- .Integer(command) + out <- .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.GetSize"), + c("CharArray","Integer"), + list(nodeLabel, NA)) + nodeSize <- out[[2]] if(nodeSize == -1) stop(nodeLabel, " is not a node in BUGS model") - command <- "BugsRobjects.GetValues" - .C("RealArray", command, nchar(command), as.double(rep(NA, nodeSize)), - as.integer(nodeSize), integer(1), NAOK = TRUE, PACKAGE="BRugs")[[3]] + numChains <- getNumChains() + out <- .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.GetValues"), + c("CharArray","RealArray"), + list(nodeLabel, double(nodeSize*numChains))) + values <- matrix(out[[2]], nrow=nodeSize, ncol=numChains) + values } infoNodeMethods <- function(nodeLabel) Added: branches/linux/BRugs/R/internal-linux.R =================================================================== --- branches/linux/BRugs/R/internal-linux.R (rev 0) +++ branches/linux/BRugs/R/internal-linux.R 2010-08-07 19:37:04 UTC (rev 164) @@ -0,0 +1,36 @@ +dquote <- function(x){ + paste("\"", x, "\"", sep="") +} + +.OpenBUGS.Linux <- function(cmds, cmdtypes, args) +{ + ncmds <- length(cmds) + if (ncmds > 99999) stop("Maximum number of OpenBUGS API commands exceeded") + tempDir <- getOption("BRugsTmpdir") + ## Don't want internalize/externalize to overwrite the command + ## output buffer, so redirect its output to a separate trash can. + trashDir <- paste(tempDir, "_trash", sep="") + extFile <- getOption("BRugsExtFile") + pkgPath <- searchpaths()[search()=="package:BRugs"] + bugsPath <- paste(pkgPath, "/exec/BugsHelper", sep="") + shcmd <- paste(bugsPath, dquote(tempDir), dquote(trashDir), dquote(extFile)) + for (i in 1:ncmds) { + if (cmdtypes[i] %in% c("CharArray","RealArray")) + cat(args[[i]], file=paste(tempDir, "/input",i,".txt", sep="")) + cmdtype <- match(cmdtypes[i], .OpenBUGS.cmdtypes) - 1 + shcmd <- paste(shcmd, dquote(cmds[i]), cmdtype) + } + res <- system(shcmd) + handleRes(res) + out <- vector(ncmds, mode="list") + for (i in 1:ncmds) { + if (cmdtypes[i] %in% c("Integer","CharArray","RealArray")) + out[[i]] <- scan(paste(tempDir,"/output",i,".txt",sep=""), + switch(cmdtypes[i], + "Integer" = integer(), + "CharArray" = character(), + "RealArray" = double()), + quiet=TRUE) + } + out +} Added: branches/linux/BRugs/R/internal-win.R =================================================================== --- branches/linux/BRugs/R/internal-win.R (rev 0) +++ branches/linux/BRugs/R/internal-win.R 2010-08-07 19:37:04 UTC (rev 164) @@ -0,0 +1,33 @@ +### Run a list of OpenBUGS API command strings + +.OpenBUGS.Windows <- function(cmds, cmdtypes, args) +{ + ncmds <- length(cmds) + out <- vector(ncmds, mode="list") + for (i in 1:ncmds) { + out[[i]] <- switch(cmdtypes[i], + "CmdInterpreter" = { + res <- .C("CmdInterpreter", cmds[i], nchar(cmds[i]), integer(1), PACKAGE = "BRugs") + handleRes(res[[3]]) + res + }, + "Integer" = { + values <- .C("Integer", cmds[i], nchar(cmds[i]), integer(1), integer(1), PACKAGE = "BRugs") + handleRes(values[[4]]) + as.integer(values[[3]]) + }, + "CharArray" = { + values <- .C("CharArray", cmds[i], nchar(cmds[i]), args[[i]], nchar(args[[i]]), integer(1), PACKAGE="BRugs") + handleRes(values[[5]]) + values[[3]] + }, + "RealArray" = { + values <- .C("RealArray", cmds[i], nchar(cmds[i]), args[[i]], length(args[[i]]), integer(1), PACKAGE="BRugs") + handleRes(values[[5]]) + values[[3]] + }) + + } + out +} + Modified: branches/linux/BRugs/R/internal.R =================================================================== --- branches/linux/BRugs/R/internal.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/internal.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,18 +1,40 @@ +### Functions to run a single OpenBUGS API command string + .CmdInterpreter <- function(command) -{ - command <- as.character(command) - res <- .C("CmdInterpreter", command, nchar(command), integer(1), PACKAGE = "BRugs") - handleRes(res[[3]]) - return(res) +{ + unlist(.OpenBUGS(command, "CmdInterpreter")) } .Integer <- function(command) { - values <- .C("Integer", command, nchar(command), integer(1), integer(1), PACKAGE = "BRugs") - handleRes(values[[4]]) - as.integer(values[[3]]) + unlist(.OpenBUGS(command, "Integer")) } +.CharArray <- function(command, arg) +{ + unlist(.OpenBUGS(command, "CharArray", arg)) +} + +.RealArray <- function(command, arg) +{ + unlist(.OpenBUGS(command, "RealArray", arg)) +} + + +.OpenBUGS.cmdtypes <- c("CmdInterpreter","Integer","CharArray","RealArray") + +.OpenBUGS <- function(cmds, cmdtypes=NULL, args=NULL) { + ncmds <- length(cmds) + if (is.null(cmdtypes)) cmdtypes <- rep("CmdInterpreter", ncmds) + if (is.null(args)) args <- as.list(rep(NA, ncmds)) + stopifnot(ncmds==length(cmdtypes)) + stopifnot(ncmds==length(args)) + switch(Sys.info()["sysname"], + "Linux" = .OpenBUGS.Linux(cmds, cmdtypes, args), + "Windows" = .OpenBUGS.Windows(cmds, cmdtypes, args), + stop("Only Linux and Windows are supported")) +} + handleRes <- function(res) { switch(res, @@ -20,3 +42,18 @@ stop("An OpenBUGS procedure was called with the wrong type of argument."), stop("An OpenBUGS procedure was called with the wrong signature.")) } + +.SamplesGlobalsCmd <- function(node){ + options.old <- options() + options(scipen=20) # don't pass numbers in scientific notation to OpenBUGS + commands <- c(paste("SamplesEmbed.beg :=", getOption("BRugsSamplesBeg")), + paste("SamplesEmbed.end :=", getOption("BRugsSamplesEnd")), + paste("SamplesEmbed.firstChain :=", getOption("BRugsSamplesFirstChain")), + paste("SamplesEmbed.lastChain :=", getOption("BRugsSamplesLastChain")), + paste("SamplesEmbed.thin :=", getOption("BRugsSamplesThin")), + paste("SamplesEmbed.SetVariable(", shQuote(node), ")", sep=""), + paste("BugsMappers.SetPrec(", getOption("BRugsPrec"), ")", sep="") + ) + options(options.old) + paste(commands, collapse="; ") +} Modified: branches/linux/BRugs/R/model.check.R =================================================================== --- branches/linux/BRugs/R/model.check.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.check.R 2010-08-07 19:37:04 UTC (rev 164) @@ -16,6 +16,7 @@ command <- gsub ("//", "/", command) } .CmdInterpreter(command) + .initGlobals() if(getOption("BRugsVerbose")) buffer() } Modified: branches/linux/BRugs/R/model.compile.R =================================================================== --- branches/linux/BRugs/R/model.compile.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.compile.R 2010-08-07 19:37:04 UTC (rev 164) @@ -10,6 +10,7 @@ .CmdInterpreter(command) samplesSetFirstChain(1) samplesSetLastChain(numChains) + options("BRugsNextChain" = 1) if(getOption("BRugsVerbose")) buffer() } Deleted: branches/linux/BRugs/R/model.getRN.R =================================================================== --- branches/linux/BRugs/R/model.getRN.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.getRN.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +0,0 @@ -"modelGetRN" <- -function() -# Get the seed of random number generator -{ - command <- "BugsEmbed.preSet" - .Integer(command) -} Modified: branches/linux/BRugs/R/model.inits.R =================================================================== --- branches/linux/BRugs/R/model.inits.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.inits.R 2010-08-07 19:37:04 UTC (rev 164) @@ -31,6 +31,7 @@ cat("Initializing chain ", chainNum[i], ": ", sep="") buffer() } + options("BRugsNextChain" = chainNum[i] + 1) } invisible() } Modified: branches/linux/BRugs/R/model.names.R =================================================================== --- branches/linux/BRugs/R/model.names.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.names.R 2010-08-07 19:37:04 UTC (rev 164) @@ -6,15 +6,29 @@ number <- .Integer(command) name <- character(number) if(length(number)){ - for(i in 1:number){ - command <- paste("BugsRobjects.SetIndex(", i-1, ")", sep="") - .CmdInterpreter(command) - command <- "BugsRobjects.GetStringLength" - numchar <- .Integer(command) - command <- "BugsRobjects.GetVariable" - char <- paste(rep(" ", numchar), collapse="") - name[i] <- .C("CharArray", command, nchar(command), char, numchar, integer(1), PACKAGE="BRugs")[[3]] - } + cmds <- character(0) + cmdtype <- character() + for(i in 1:number){ + cmds <- c(cmds, paste("BugsRobjects.SetIndex(", i-1, ")", sep=""), + "BugsRobjects.GetStringLength") + cmdtype <- c(cmdtype, c("CmdInterpreter","Integer")) + } + res <- .OpenBUGS(cmds, cmdtype) + numchar <- unlist(res[seq(2, 2*number, by=2)]) + + cmds <- character(0) + cmdtype <- character() + args <- list() + for(i in 1:number){ + char <- paste(rep(" ", numchar[i]), collapse="") + cmds <- c(cmds, + paste("BugsRobjects.SetIndex(", i-1, ")", sep=""), + "BugsRobjects.GetVariable") + cmdtype <- c(cmdtype, c("CmdInterpreter","CharArray")) + args <- c(args, list(NA, char)) + } + res <- .OpenBUGS(cmds, cmdtype, args) + name <- unlist(res[seq(2, 2*number, by=2)]) } return(name) -} + } Modified: branches/linux/BRugs/R/model.precision.R =================================================================== --- branches/linux/BRugs/R/model.precision.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.precision.R 2010-08-07 19:37:04 UTC (rev 164) @@ -5,6 +5,7 @@ if(!is.numeric(prec)) stop("prec ", "must be numeric") prec <- as.integer(prec) - command <- paste("BugsMappers.SetPrec(", prec, ")") - invisible(.CmdInterpreter(command)) + options(BRugsPrec=prec) +# command <- paste("BugsMappers.SetPrec(", prec, ")") +# invisible(.CmdInterpreter(command)) } Modified: branches/linux/BRugs/R/model.setRN.R =================================================================== --- branches/linux/BRugs/R/model.setRN.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/model.setRN.R 2010-08-07 19:37:04 UTC (rev 164) @@ -6,9 +6,5 @@ stop("state must be an integer from 1 to 14") state <- as.integer(state) command <- paste("BugsEmbed.SetRNGuard; BugsEmbed.SetRNState(", state, ")" ) - res <- .CmdInterpreter(command)[[3]] - if(!res){ - if(getOption("BRugsVerbose")) - message("Random number generator state successfully set") - }else stop("Setting random number generator state returned with an error.") + invisible(.CmdInterpreter(command)) } Modified: branches/linux/BRugs/R/plot.bgr.R =================================================================== --- branches/linux/BRugs/R/plot.bgr.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/plot.bgr.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,13 +1,42 @@ "plotBgr" <- -function(node, plot = TRUE, main = NULL, xlab = "iteration", ylab = "bgr", - col = c("red", "blue", "green"), bins = 50, ...) -# Plot bgr diagnostic for single component of OpenBUGS name + function(node, plot = TRUE, main = NULL, xlab = "iteration", ylab = "bgr", + col = c("red", "blue", "green"), bins = 50, ...) + # Plot bgr diagnostic for single component of OpenBUGS name { sM <- samplesMonitors(node) if(length(sM) > 1 || sM != node) stop("node must be a scalar variable from the model, for arrays use samplesBgr") grid <- bgrGrid(node, bins = bins) - bgr <- sapply(grid, bgrPoint, node = node) + + ## Use a single API call instead of looping API calls over + ## iterations - more efficient with the Linux helper. + + ## find size of available sample at each grid point + res <- .OpenBUGS(cmds = c(.SamplesGlobalsCmd(node), + as.vector(rbind(paste("SamplesEmbed.end := ", grid, ";"), "SamplesEmbed.SampleSize;"))), + cmdtypes = c("CmdInterpreter", rep(c("CmdInterpreter","Integer"), bins)), + args=as.list(c(NA, rep(c(NA, NA), bins))) + ) + + args <- list(NA) + for (i in seq(length=bins)){ + args[[2*i]] <- NA + args[[2*i + 1]] <- double(res[[2*i + 1]]) + } + + ## get available sample at each grid point + res <- .OpenBUGS(cmds = + c(.SamplesGlobalsCmd(node), + as.vector(rbind(paste("SamplesEmbed.end := ", grid, ";"), "SamplesEmbed.SampleValues;"))), + cmdtypes = c("CmdInterpreter", rep(c("CmdInterpreter","RealArray"), bins)), + args=args) + + ## remove junk elements of list, leaving a list of samples for each grid point + res[c(1, 2*seq(length=bins))] <- NULL + + ## calculate between, within and ratio statistics for each grid point + bgr <- rbind(grid, sapply(res, bgrPoint)) + yRange <- range(bgr[4,]) yRange <- c(0, max(c(1.2, yRange[2]))) nRange <- range(bgr[2,]) @@ -21,7 +50,7 @@ bgr[3,] <- bgr[3,] / max if(plot){ plot(grid, bgr[4,], ylim = yRange, type = "l", - main = if(is.null(main)) node else main, xlab = xlab, ylab = ylab, col = col[1], ...) + main = if(is.null(main)) node else main, xlab = xlab, ylab = ylab, col = col[1], ...) lines(grid, bgr[2,], col = col[2], ...) lines(grid, bgr[3,], col = col[3], ...) } @@ -30,4 +59,5 @@ bgr$Iteration <- as.integer(bgr$Iteration) if(plot) invisible(bgr) else return(bgr) + } Modified: branches/linux/BRugs/R/samples.coda.R =================================================================== --- branches/linux/BRugs/R/samples.coda.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.coda.R 2010-08-07 19:37:04 UTC (rev 164) @@ -29,9 +29,8 @@ samplesSetLastChain(lastChain) thin <- max(c(thin, 1)) samplesSetThin(thin) - command <- paste("SamplesEmbed.SetVariable(", sQuote(node), - ");SamplesEmbed.StatsGuard;", "SamplesEmbed.CODA(", - sQuote(stem), ")") + command <- paste(.SamplesGlobalsCmd(node), ";SamplesEmbed.StatsGuard;", + "SamplesEmbed.CODA(", sQuote(stem), ")") .CmdInterpreter(command) buffer() } Modified: branches/linux/BRugs/R/samples.correl.R =================================================================== --- branches/linux/BRugs/R/samples.correl.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.correl.R 2010-08-07 19:37:04 UTC (rev 164) @@ -22,10 +22,16 @@ samplesSetLastChain(lastChain) thin <- max(c(thin, 1)) samplesSetThin(thin) - - command <- paste("CorrelEmbed.SetVariable0(", sQuote(node0), - ");CorrelEmbed.SetVariable1(", sQuote(node1), - ");CorrelEmbed.Guard", ";CorrelEmbed.PrintMatrix") + + command <- paste("CorrelEmbed.beg :=", getOption("BRugsSamplesBeg"), + "; CorrelEmbed.end :=", getOption("BRugsSamplesEnd"), + "; CorrelEmbed.firstChain :=", getOption("BRugsSamplesFirstChain"), + "; CorrelEmbed.lastChain :=", getOption("BRugsSamplesLastChain"), + "; CorrelEmbed.thin :=", getOption("BRugsSamplesThin"), + "; CorrelEmbed.SetVariable0(", sQuote(node0), + ");CorrelEmbed.SetVariable1(", sQuote(node1), + ");CorrelEmbed.Guard", ";CorrelEmbed.PrintMatrix" + ) .CmdInterpreter(command) buffer <- file.path(tempdir(), "buffer.txt") rlb <- readLines(buffer) Modified: branches/linux/BRugs/R/samples.get.beg.R =================================================================== --- branches/linux/BRugs/R/samples.get.beg.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.get.beg.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +1,6 @@ "samplesGetBeg" <- function() -# Get the beg field +# Beginning iteration from which to compute sample statistics { - command <- "SamplesEmbed.beg" - .Integer(command) + getOption("BRugsSamplesBeg") } Modified: branches/linux/BRugs/R/samples.get.end.R =================================================================== --- branches/linux/BRugs/R/samples.get.end.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.get.end.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +1,6 @@ "samplesGetEnd" <- function() -# Get the end field +# End iteration from which to compute sample statistics { - command <- "SamplesEmbed.end" - .Integer(command) + getOption("BRugsSamplesEnd") } Modified: branches/linux/BRugs/R/samples.get.firstChain.R =================================================================== --- branches/linux/BRugs/R/samples.get.firstChain.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.get.firstChain.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +1,6 @@ "samplesGetFirstChain" <- function() -# Get the firstChain field +# First chain from which to compute sample statistics { - command <- "SamplesEmbed.firstChain" - .Integer(command) + getOption("BRugsSamplesFirstChain") } Modified: branches/linux/BRugs/R/samples.get.lastChain.R =================================================================== --- branches/linux/BRugs/R/samples.get.lastChain.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.get.lastChain.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +1,6 @@ "samplesGetLastChain" <- function() -# Get the lastChain field +# Last chain from which to compute sample statistics { - command <- "SamplesEmbed.lastChain" - .Integer(command) + getOption("BRugsSamplesLastChain") } Modified: branches/linux/BRugs/R/samples.get.thin.R =================================================================== --- branches/linux/BRugs/R/samples.get.thin.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.get.thin.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,7 +1,6 @@ "samplesGetThin" <- function() -# Get the thin field +# Thinning interval to apply to sample statistics { - command <- "SamplesEmbed.thin" - .Integer(command) + getOption("BRugsSamplesThin") } Modified: branches/linux/BRugs/R/samples.monitors.R =================================================================== --- branches/linux/BRugs/R/samples.monitors.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.monitors.R 2010-08-07 19:37:04 UTC (rev 164) @@ -4,7 +4,7 @@ { if (is.R()){ command <- paste("SamplesEmbed.SetVariable(", sQuote(node), - ");SamplesEmbed.StatsGuard;SamplesEmbed.Labels") + ");SamplesEmbed.StatsGuard;SamplesEmbed.Labels",sep="") .CmdInterpreter(command) buffer <- file.path(tempdir(), "buffer.txt") rlb <- readLines(buffer) @@ -23,7 +23,7 @@ } else { sampsMonsSingle <- function(node){ command <- paste("SamplesEmbed.SetVariable(", sQuote(node), - ");SamplesEmbed.StatsGuard;SamplesEmbed.Labels") + ");SamplesEmbed.StatsGuard;SamplesEmbed.Labels",sep="") .CmdInterpreter(command) buffer <- file.path(tempdir(), "buffer.txt") rlb <- readLines(buffer) Modified: branches/linux/BRugs/R/samples.sample.R =================================================================== --- branches/linux/BRugs/R/samples.sample.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.sample.R 2010-08-07 19:37:04 UTC (rev 164) @@ -9,16 +9,14 @@ sM <- samplesMonitors(node)[1] if(sM == "model must be initialized before monitors used") stop("model must be initialized / updated / monitored before samplesSample is used") - - command <- "BugsRobjects.SetVariable" - .C("CharArray", command, nchar(command), node, nchar(node), integer(1), PACKAGE="BRugs") - command <- "BugsRobjects.GetSize" - nodeSize <- .Integer(command) - if(nodeSize > 1) + nodeSize <- .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.GetSize"), + c("CharArray","Integer"), + list(node,NA))[[2]] + if(nodeSize > 1) stop("Only scalar nodes such as ", node, "[1] are allowed.") - sampleSize <- samplesSize(node) - command <- "SamplesEmbed.SampleValues" - .C("RealArray", command, nchar(command), - double(sampleSize), sampleSize, integer(1), PACKAGE="BRugs")[[3]] + sample <- .OpenBUGS(c(.SamplesGlobalsCmd(node), "SamplesEmbed.SampleValues"), + c("CmdInterpreter","RealArray"), + list(node,double(sampleSize)))[[2]] + sample } Modified: branches/linux/BRugs/R/samples.set.beg.R =================================================================== --- branches/linux/BRugs/R/samples.set.beg.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.set.beg.R 2010-08-07 19:37:04 UTC (rev 164) @@ -5,6 +5,5 @@ if(!is.numeric(begIt)) stop("begIt ", "must be numeric") begIt <- as.integer(begIt) - command <- paste("SamplesEmbed.beg :=", begIt) - invisible(.CmdInterpreter(command)) + options("BRugsSamplesBeg" = begIt) } Modified: branches/linux/BRugs/R/samples.set.end.R =================================================================== --- branches/linux/BRugs/R/samples.set.end.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.set.end.R 2010-08-07 19:37:04 UTC (rev 164) @@ -5,6 +5,5 @@ if(!is.numeric(endIt)) stop("endIt ", "must be numeric") endIt <- as.integer(endIt) - command <- paste("SamplesEmbed.end :=", endIt) - invisible(.CmdInterpreter(command)) + options("BRugsSamplesEnd" = endIt) } Modified: branches/linux/BRugs/R/samples.set.firstChain.R =================================================================== --- branches/linux/BRugs/R/samples.set.firstChain.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.set.firstChain.R 2010-08-07 19:37:04 UTC (rev 164) @@ -7,6 +7,5 @@ first <- as.integer(first) if(!(first %in% 1:getNumChains())) stop("it is required to have 1 <= first <= nchains") - command <- paste("SamplesEmbed.firstChain :=", as.integer(first)) - invisible(.CmdInterpreter(command)) + options("BRugsSamplesFirstChain" = first) } Modified: branches/linux/BRugs/R/samples.set.lastChain.R =================================================================== --- branches/linux/BRugs/R/samples.set.lastChain.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.set.lastChain.R 2010-08-07 19:37:04 UTC (rev 164) @@ -7,6 +7,5 @@ last <- as.integer(last) if(!(last %in% 1:getNumChains())) stop("it is required to have 1 <= last <= nchains") - command <- paste("SamplesEmbed.lastChain :=", last) - invisible(.CmdInterpreter(command)) + options("BRugsSamplesLastChain" = last) } Modified: branches/linux/BRugs/R/samples.set.thin.R =================================================================== --- branches/linux/BRugs/R/samples.set.thin.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.set.thin.R 2010-08-07 19:37:04 UTC (rev 164) @@ -4,6 +4,5 @@ { if(!is.numeric(thin)) stop("thin ", "must be numeric") - command <- paste("SamplesEmbed.thin :=", as.integer(thin)) - invisible(.CmdInterpreter(command)) + options("BRugsSamplesThin" = thin) } Modified: branches/linux/BRugs/R/samples.size.R =================================================================== --- branches/linux/BRugs/R/samples.size.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.size.R 2010-08-07 19:37:04 UTC (rev 164) @@ -9,8 +9,7 @@ if (any(grep("^model has probably not yet been updated", sM))) return(0) if(length(sM) > 1 || sM != node) stop("node must be a scalar variable from the model") - command <- paste("SamplesEmbed.SetVariable(", shQuote(node), ")") - .CmdInterpreter(command) - command <- "SamplesEmbed.SampleSize" - .Integer(command) + size <- .OpenBUGS(c(.SamplesGlobalsCmd(node), "SamplesEmbed.SampleSize"), + c("CmdInterpreter","Integer"))[[2]] + size } Modified: branches/linux/BRugs/R/samples.stats.R =================================================================== --- branches/linux/BRugs/R/samples.stats.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/samples.stats.R 2010-08-07 19:37:04 UTC (rev 164) @@ -22,7 +22,6 @@ samplesSetLastChain(lastChain) thin <- max(c(thin, 1)) samplesSetThin(thin) - nodeName <- sQuote(node) if (is.R()){ result <- data.frame(mean=NULL, sd=NULL, MC_error = NULL, val2.5pc=NULL, @@ -33,9 +32,8 @@ start = numeric(), sample=numeric()) } - for(i in seq(along=nodeName)){ - command <- paste("SamplesEmbed.SetVariable(", nodeName[i], - ");SamplesEmbed.StatsGuard;SamplesEmbed.Stats") + for(i in seq(along=node)){ + command <- paste(.SamplesGlobalsCmd(node), "SamplesEmbed.StatsGuard;SamplesEmbed.Stats") .CmdInterpreter(command) buffer <- file.path(tempdir(), "buffer.txt") rlb <- readLines(buffer) @@ -44,9 +42,9 @@ result <- rbind(result, read.table(buffer)) else{ if(length(grep("val97.5pc", rlb))) - message("Variable ", nodeName[i], " has probably not been updated") + message("Variable ", node[i], " has probably not been updated") else - message("Variable ", nodeName[i], ": ", rlb) + message("Variable ", node[i], ": ", rlb) } } return(result) Modified: branches/linux/BRugs/R/set.values.R =================================================================== --- branches/linux/BRugs/R/set.values.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/set.values.R 2010-08-07 19:37:04 UTC (rev 164) @@ -8,19 +8,16 @@ # if(any(DoNotSetNA)) # warning("Some NA values formerly had a non-NA value -- left unchanged") # values[DoNotSetNA] <- cv[DoNotSetNA] - if (dimensions(nodeLabel) == 0) - stop("Only allowed for vector, not scalar nodes") - command <- "BugsRobjects.SetVariable" - .C("CharArray", command, nchar(command), nodeLabel, nchar(nodeLabel), integer(1), PACKAGE="BRugs") - command <- "BugsRobjects.GetSize" - nodeSize <- .Integer(command) + nodeSize <- .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.GetSize"), + c("CharArray","Integer"), + c(nodeLabel,NA))[[2]] if(nodeSize == -1) stop(nodeLabel, " is not a node in BUGS model") - if(length(values) != nodeSize) - stop("length(values) does not correspond to the node size") - command <- "BugsRobjects.SetValues" - res <- .C("RealArray", command, nchar(command), as.double(values), as.integer(nodeSize), - integer(1), NAOK = TRUE, PACKAGE="BRugs") - handleRes(res[[5]]) + numChains <- getNumChains() + if(length(values) != nodeSize*numChains) + stop("length(values) does not correspond to the node size and number of chains") + .OpenBUGS(c("BugsRobjects.SetVariable", "BugsRobjects.SetValues"), + c("CharArray","RealArray"), + list(nodeLabel,as.double(values)))[[2]] invisible() } Modified: branches/linux/BRugs/R/zzz.R =================================================================== --- branches/linux/BRugs/R/zzz.R 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/R/zzz.R 2010-08-07 19:37:04 UTC (rev 164) @@ -1,27 +1,62 @@ if (is.R()){ - ".onLoad" <- function(lib, pkg){ + .initGlobals <- function(){ + options("BRugsSamplesBeg" = 1) + options("BRugsSamplesEnd" = 10000000) + options("BRugsSamplesFirstChain" = 1) + options("BRugsSamplesLastChain" = 1) + options("BRugsSamplesThin" = 1) + options("BRugsSamplesVariable" = "*") + options("BRugsNextChain" = 1) # index of chain which needs to be initialized next + options("BRugsPrec" = 4) + } + + .onLoad <- function(...) { + switch(Sys.info()["sysname"], + "Linux" = .onLoad.Linux(...), + "Windows" = .onLoad.Windows(...), + stop("Only Linux and Windows are supported")) + if(is.null(getOption("BRugsVerbose"))) + options("BRugsVerbose" = TRUE) + .initGlobals() + } + + ".onLoad.Windows" <- function(lib, pkg){ ## sets path / file variables and initializes subsystems root <- file.path(system.file("OpenBUGS", package=pkg)) - ## we do have a NAMESPACE now: library.dynam("BRugs", pkg, lib) + library.dynam("BRugs", pkg, lib) len <- nchar(root) tempDir <- gsub("\\\\", "/", tempdir()) .C("SetWorkingDir", as.character(root), len, PACKAGE="BRugs") .C("SetTempDir", as.character(tempDir), nchar(tempDir), PACKAGE="BRugs") command <- "BugsMappers.SetDest(2)" .CmdInterpreter(command) - if(is.null(getOption("BRugsVerbose"))) - options("BRugsVerbose" = TRUE) } + + ".onLoad.Linux" <- function(lib, pkg){ + ## TODO any need for these to be user specifiable? + options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) + options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) + } ".onAttach" <- function(lib, pkg){ - message("Welcome to BRugs running on OpenBUGS version 3.1.0") + message("Welcome to BRugs running on OpenBUGS version 3.1.2") } - - ".onUnload" <- function(libpath){ + + .onUnload <- function(...) { + switch(Sys.info()["sysname"], + "Linux" = .onUnload.Linux(...), + "Windows" = .onUnload.Windows(...), + stop("Only Linux and Windows are supported")) + } + + ".onUnload.Windows" <- function(libpath){ library.dynam.unload("BRugs", libpath) } + ".onUnload.Linux" <- function(libpath){ + } + ## Overwriting new (from R-2.6.0) sQuote (for typing human readable text) in R within the BRugs Namespace! ## we cannot use sQuote that uses fancy quotes! sQuote <- function(x) paste("'", x, "'", sep="") Deleted: branches/linux/BRugs/configure =================================================================== --- branches/linux/BRugs/configure 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/configure 2010-08-07 19:37:04 UTC (rev 164) @@ -1,3 +0,0 @@ -echo "Package 'BRugs' currently only works under Windows.\nIt is supposed to work under Linux in future releases." -exit 1 - Deleted: branches/linux/BRugs/configure.win =================================================================== Modified: branches/linux/BRugs/man/BRugs.Rd =================================================================== --- branches/linux/BRugs/man/BRugs.Rd 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/man/BRugs.Rd 2010-08-07 19:37:04 UTC (rev 164) @@ -1,43 +1,43 @@ -\name{BRugs} +\name{BRugs} \alias{BRugs} \alias{help.BRugs} -\title{Introduction to BRugs} -\description{This manual describes how to use the BRugs software} +\title{Introduction to BRugs} +\description{This manual describes how to use the BRugs software} \usage{ help.BRugs(browser = getOption("browser")) } \arguments{ -\item{browser}{the name of the program to be used as hypertext browser. +\item{browser}{the name of the program to be used as hypertext browser. It should be in the PATH, or a full path specified.} } \details{ - BRugs is a collection of R functions that - allow users to analyze graphical models using MCMC techniques. Most of the R functions in BRugs provide a - interface to the BRugs dynamic link library (shared object file). The BRugs dynamic link library is able to make - use of many of the WinBUGS components, in particular those components concerned with graphical models and MCMC - simulation. BRugs lacks the GUI interface of WinBUGS but is able to use R to create graphical displays of the - MCMC simulation. BRugs uses the same model specification language as WinBUGS and the same format for data and - initial values. However BRugs always uses plain text files for input inplace of WinBUGS compound documents. The - BRugs functions can be split into two groups: those associated with setting up and simulating the graphical model - and those associated with making statistical inference. In general the R functions in BRugs correspond to the - command buttons and text entry fields in the menus of WinBUGS. Each WinBUGS text entry field splits into two + BRugs is a collection of R functions that + allow users to analyze graphical models using MCMC techniques. Most of the R functions in BRugs provide a + interface to the BRugs dynamic link library (shared object file). The BRugs dynamic link library is able to make + use of many of the WinBUGS components, in particular those components concerned with graphical models and MCMC + simulation. BRugs lacks the GUI interface of WinBUGS but is able to use R to create graphical displays of the + MCMC simulation. BRugs uses the same model specification language as WinBUGS and the same format for data and + initial values. However BRugs always uses plain text files for input inplace of WinBUGS compound documents. The + BRugs functions can be split into two groups: those associated with setting up and simulating the graphical model + and those associated with making statistical inference. In general the R functions in BRugs correspond to the + command buttons and text entry fields in the menus of WinBUGS. Each WinBUGS text entry field splits into two R functions, one to set the quantity and the other to get the value of the quantity. - - Andrew Gelman suggests to use the function \code{bugs} in the \pkg{R2WinBUGS} package + + Andrew Gelman suggests to use the function \code{bugs} in the \pkg{R2WinBUGS} package with argument \code{program="openbugs"} as a wrapper. } \section{Permission and Disclaimer}{ - BRugs is released under the GNU GENERAL PUBLIC LICENSE. + BRugs is released under the GNU GENERAL PUBLIC LICENSE. For details see \url{http://mathstat.helsinki.fi/openbugs/} or type \code{help.BRugs()}. - More informally, potential users are reminded to be extremely careful if using this program for serious - statistical analysis. We have tested the program on quite a wide set of examples, but be particularly careful - with types of model that are currently not featured. If there is a problem, BRugs might just crash, which is not - very good, but it might well carry on and produce answers that are wrong, which is even worse. Please let us know + More informally, potential users are reminded to be extremely careful if using this program for serious + statistical analysis. We have tested the program on quite a wide set of examples, but be particularly careful + with types of model that are currently not featured. If there is a problem, BRugs might just crash, which is not + very good, but it might well carry on and produce answers that are wrong, which is even worse. Please let us know of any successes or failures. -} +} %\references{} -\seealso{\code{\link{help.WinBUGS}} (which currently is called from \code{help.BRugs}) and the meta function \code{\link{BRugsFit}}} +\seealso{\code{\link{help.WinBUGS}} (which currently is called from \code{help.BRugs}) and the meta function \code{\link{BRugsFit}}} \examples{ ### Step by step example: ### library(BRugs) # loading BRugs @@ -47,10 +47,10 @@ setwd(system.file("OpenBUGS", "Examples", package="BRugs")) ## some usual steps (like clicking in WinBUGS): -modelCheck("ratsmodel.txt") # check model file -modelData("ratsdata.txt") # read data file +modelCheck("Ratsmodel.txt") # check model file +modelData("Ratsdata.txt") # read data file modelCompile(numChains=2) # compile model with 2 chains -modelInits(rep("ratsinits.txt", 2)) # read init data file +modelInits(rep("Ratsinits.txt", 2)) # read init data file modelUpdate(1000) # burn in samplesSet(c("alpha0", "alpha")) # alpha0 and alpha should be monitored modelUpdate(1000) # 1000 more iterations .... @@ -64,11 +64,11 @@ samplesAutoC("alpha[1:6]", 1) # plot autocorrelations of 1st chain ## switch back to the previous working directory: -setwd(oldwd) +setwd(oldwd) \dontrun{ # Getting more (online-)help: if (is.R()) - help.BRugs() + help.BRugs() } } \keyword{interface} Modified: branches/linux/BRugs/man/BRugsFit.Rd =================================================================== --- branches/linux/BRugs/man/BRugsFit.Rd 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/man/BRugsFit.Rd 2010-08-07 19:37:04 UTC (rev 164) @@ -52,8 +52,8 @@ Andrew Gelman proposes some \code{print} and \code{plot} methods that can be accessed by the \code{openbugs} (and \code{bugs}) and \code{as.bugs.array} functions in the CRAN package \pkg{R2WinBUGS}.} \examples{ -BRugsFit(data = "ratsdata.txt", inits = "ratsinits.txt", - para = c("alpha", "beta"), modelFile = "ratsmodel.txt", +BRugsFit(data = "Ratsdata.txt", inits = "Ratsinits.txt", + para = c("alpha", "beta"), modelFile = "Ratsmodel.txt", numChains = 1, working.directory = system.file("OpenBUGS", "Examples", package = "BRugs")) Modified: branches/linux/BRugs/man/bgr.point.Rd =================================================================== --- branches/linux/BRugs/man/bgr.point.Rd 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/man/bgr.point.Rd 2010-08-07 19:37:04 UTC (rev 164) @@ -7,12 +7,13 @@ } \usage{ bgrGrid(node, bins = 50) -bgrPoint(node, iteration) +bgrPoint(sample) } \arguments{ \item{node}{Character vector of length 1, name of a variable in the model.} \item{bins}{Blocksize} - \item{iteration}{Calculated by \code{bgrGrid}} + \item{sample}{Monitored sample from multiple chains to calculate the + convergence statistic for.} } \note{Intended for internal use only.} \seealso{\code{\link{samplesBgr}}, \code{\link{BRugs}}, \code{\link{help.WinBUGS}}} Modified: branches/linux/BRugs/man/model.RN.Rd =================================================================== --- branches/linux/BRugs/man/model.RN.Rd 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/man/model.RN.Rd 2010-08-07 19:37:04 UTC (rev 164) @@ -1,11 +1,9 @@ \name{modelRN} \alias{modelSetRN} -\alias{modelGetRN} \title{State of Random Number Generator} -\description{These functions set/return the starting state of the random number generator.} +\description{Set the starting state of the random number generator.} \usage{ modelSetRN(state) -modelGetRN() } \arguments{ \item{state}{An integer from 1 to 14. The internal state of the OpenBUGS random number generator can be set to one of 14 predefined states. Each predefined state is \eqn{10^12}{10^12} draws apart to avoid overlap in random number sequences.} Modified: branches/linux/BRugs/man/set.values.Rd =================================================================== --- branches/linux/BRugs/man/set.values.Rd 2010-08-07 18:10:35 UTC (rev 163) +++ branches/linux/BRugs/man/set.values.Rd 2010-08-07 19:37:04 UTC (rev 164) @@ -2,12 +2,13 @@ \alias{setValues} \title{Setting current values} \description{This function sets the current values of a variable for future - iterations. Only supported for vector, not scalar nodes.} + iterations. Only stochastic nodes can be set using this facility, and + logical nodes are then updated if necessary. } \usage{ setValues(nodeLabel, values) } \arguments{ - \item{nodeLabel}{Character vector of length 1, name of a vector node in the model.} + \item{nodeLabel}{Character vector of length 1, name of a node in the model.} \item{values}{The values to be set, generated, e.g., by \code{\link{infoNodeValues}}.} } \details{ Added: branches/linux/BRugs/src/BugsHelper.c =================================================================== --- branches/linux/BRugs/src/BugsHelper.c (rev 0) +++ branches/linux/BRugs/src/BugsHelper.c 2010-08-07 19:37:04 UTC (rev 164) @@ -0,0 +1,300 @@ +/* BugsHelper - Perform one or more OpenBUGS API commands as specified +in the command line arguments. + +ARGUMENTS (not named) + + argv[1]: Full path to temporary directory containing the buffer file + for messages from the main API commands, and any input and output + corresponding to the commands. + + argv[2]: Full path to temporary directory containing the buffer file + for messages from the Internalize and Externalize commands. We do not + want these to overwrite the main buffer. + + argv[3]: Name of the file used to store the externalized model + state. This will be saved in the directory specified in argv[1]. + + The remaining arguments argv[4], argv[5], ... specify any number of + calls to OpenBUGS API functions. These are given in the order: + + cmd, cmdtype, cmd, cmdtype, ... + + where "cmd" is an OpenBUGS API command, and "cmdtype" is an integer + specifying the API function being called. Currently allowed values of + "cmdtype" are + + 0 : if "cmd" is a call to the "CmdInterpreter" API function + 1 : if "cmd" is a call to the "Integer" API function + 2 : if "cmd" is a call to the "CharArray" API function + 3 : if "cmd" is a call to the "RealArray" API function + + +INPUT AND OUTPUT + + Some OpenBUGS commands require input or produce output. The input and + output for the Nth command given in the call to BugsHelper are stored + in files called inputN.txt and outputN.txt, and are saved in the + directory specified in argv[1]. + + +EXAMPLE + + The following command checks a BUGS model file stored in the file + /path/to/Examples/Ratsmodel.txt and then loads a data file from + /path/to/Examples/Ratsdata.txt. Temporary files are stored in + subdirectories of /tmp. + + "BugsEmbed.SetFilePath('/scratch/chris/lib/R/BRugs/OpenBUGS/Examples/Ratsdata.txt');BugsEmbed.LoadDataGuard;BugsEmbed.LoadData" 0 + + /path/to/BugsHelper "/tmp/RtmpaRQois" "/tmp/RtmpaRQois_trash" "file327b23c6.bug" "BugsEmbed.SetFilePath('/path/to/Examples/Ratsmodel.txt');BugsEmbed.ParseGuard;BugsEmbed.Parse" 0 "BugsEmbed.SetFilePath('/path/to/Examples/Ratsdata.txt');BugsEmbed.LoadDataGuard;BugsEmbed.LoadData" 0 + + +AUTHOR + + Chris Jackson <chr...@mr...> + + */ + +#include <stdio.h> +#include <string.h> +#include <stdlib.h> +#include <sys/stat.h> + +#define NODEBUG + +/* OpenBUGS API functions from libOpenBUGS.so */ +int errno; +extern void CLI (); +extern void BugsCmd(char **command, int *len); +extern void CharArray (char **procedure, int *len, char **x, int *lenX, int *res); +extern void CmdInterpreter (char **command, int *len, int *res); +extern void Guard (char **procedure, int *len, int *x, int *res); +extern void Integer (char **procedure, int *len, int *x, int *res); +extern void IntegerArray (char **procedure, int *len, int *x, int *lenX, int *res); +extern void Real (char **procedure, int *len, double *x, double *y, int *res); +extern void RealArray (char **procedure, int *len, double *x, int *lenX, int *res); +extern void SetWorkingDir (char **path, int *len); +extern void SetTempDir(char **path, int *len); +extern void UseBufferFile (); +extern void UseConsole (); + +void read_input_real(char *tmpdir, double **out, int *len, int cmdno) { + char *fname; + struct stat buf; + FILE *ifp; + double tmp; + fname = (char *) malloc(strlen(tmpdir) + 16); + sprintf(fname, "%s/input%d.txt", tmpdir, cmdno); + if (stat(fname, &buf) != -1) { + *len = 0; + ifp = fopen(fname, "r"); + while (fscanf(ifp, "%lf", &tmp) == 1) + ++*len; + *out = (double *) malloc(sizeof(double)*(*len)); +#ifdef DEBUG + printf("Reading %d values from %s\n", *len, fname); +#endif + fseek(ifp, 0, SEEK_SET); /* move to start of file */ + *len = 0; + while (fscanf(ifp, "%lf", &((*out)[*len])) == 1){ + ++*len; + } + fclose(ifp); + } + free(fname); +} + +int file_size() { +} + +void read_input_char(char *tmpdir, char **out, int *len, int cmdno) { + char *fname; + struct stat buf; + FILE *ifp; + fname = (char *) malloc(strlen(tmpdir) + 16); + sprintf(fname, "%s/input%d.txt", tmpdir, cmdno); + if (stat(fname, &buf) != -1) { + *len = buf.st_size; + *out = (char *) malloc(*len + 1); + ifp = fopen(fname, "r"); +#ifdef DEBUG + printf("Reading %d characters from %s\n", *len, fname); +#endif + *len = 0; + while(((*out)[*len] = getc(ifp)) != EOF) { + ++*len; + } + (*out)[*len] = '\0'; + fclose(ifp); + } + free(fname); +} + +void write_output_int(char *tmpdir, int out, int cmdno) { + char *fname; + FILE *ofp; + fname = (char *) malloc(strlen(tmpdir) + 16); + sprintf(fname, "%s/output%d.txt", tmpdir, cmdno); + ofp = fopen(fname, "w"); +#ifdef DEBUG + printf("Writing integer %d to %s\n", out, fname); +#endif + fprintf(ofp, "%d", out); + fclose(ofp); + free(fname); +} + +void write_output_real(char *tmpdir, double *out, int len, int cmdno) { + char *fname; + FILE *ofp; + int i; + fname = (char *) malloc(strlen(tmpdir) + 16); + sprintf(fname, "%s/output%d.txt", tmpdir, cmdno); + ofp = fopen(fname, "w"); +#ifdef DEBUG + printf("Writing %d reals to %s\n", len, fname); +#endif + for (i=0; i<len; ++i) + fprintf(ofp, "%lf ", out[i]); // TODO is precision acceptable? + fclose(ofp); + free(fname); +} + +void write_output_char(char *tmpdir, char *out, int cmdno) { + char *fname; + FILE *ofp; + fname = (char *) malloc(strlen(tmpdir) + 16); + sprintf(fname, "%s/output%d.txt", tmpdir, cmdno); +#ifdef DEBUG + printf("Writing string %s to %s\n", out, fname); +#endif + ofp = fopen(fname, "w"); + fprintf(ofp, "%s", out); + fclose(ofp); + free(fname); +} + +int do_TempDir(char *dir) { + int length; + length = strlen(dir); + SetTempDir(&dir, &length); +} + +int do_Cmd(char *cmd) { + int length, res; + length = strlen(cmd); +#ifdef DEBUG + printf("%s: %d\n", cmd, strlen(cmd)); +#endif + CmdInterpreter(&cmd, &length, &res); + return res; +} + +int do_Integer(char *cmd, char *tmpdir, int cmdno) { + int length, out, res; + // doesn't need input -- assume only used for reading integers + length = strlen(cmd); +#ifdef DEBUG + printf("%s: %d\n", cmd, strlen(cmd)); +#endif + Integer(&cmd, &length, &out, &res); + write_output_int(tmpdir, out, cmdno); + return res; +} + +int do_CharArray(char *cmd, char *tmpdir, int cmdno) { + int length, outlength, res; + char *out; + int i; + length = strlen(cmd); + read_input_char(tmpdir, &out, &outlength, cmdno); +#ifdef DEBUG + printf("%s: args=%s, arglength=%d\n", cmd, out, outlength); +#endif + CharArray(&cmd, &length, &out, &outlength, &res); + write_output_char(tmpdir, out, cmdn... [truncated message content] |
From: <chr...@us...> - 2010-09-09 09:11:59
|
Revision: 170 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=170&view=rev Author: chris-jackson Date: 2010-09-09 09:11:53 +0000 (Thu, 09 Sep 2010) Log Message: ----------- LDFLAGS added to BugsHelper compile command Modified Paths: -------------- branches/linux/BRugs/.Rbuildignore branches/linux/BRugs/src/Makevars Modified: branches/linux/BRugs/.Rbuildignore =================================================================== --- branches/linux/BRugs/.Rbuildignore 2010-09-02 16:44:16 UTC (rev 169) +++ branches/linux/BRugs/.Rbuildignore 2010-09-09 09:11:53 UTC (rev 170) @@ -1 +1,2 @@ inst/README-inst_OpenBUGS +exec/BugsHelper Modified: branches/linux/BRugs/src/Makevars =================================================================== --- branches/linux/BRugs/src/Makevars 2010-09-02 16:44:16 UTC (rev 169) +++ branches/linux/BRugs/src/Makevars 2010-09-09 09:11:53 UTC (rev 170) @@ -1,2 +1,2 @@ BugsHelper: - $(CC) $(CFLAGS) -m32 -Wl,-rpath=\$$ORIGIN/../OpenBUGS BugsHelper.c ../inst/OpenBUGS/libOpenBUGS.so -o ../exec/BugsHelper + $(CC) $(CFLAGS) $(LDFLAGS) -m32 -Wl,-rpath=\$$ORIGIN/../OpenBUGS BugsHelper.c ../inst/OpenBUGS/libOpenBUGS.so -o ../exec/BugsHelper This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <chr...@us...> - 2010-11-04 21:47:34
|
Revision: 176 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=176&view=rev Author: chris-jackson Date: 2010-11-04 21:47:27 +0000 (Thu, 04 Nov 2010) Log Message: ----------- Fix bugsData to not require a loaded model (forthcoming OpenBUGS will accept data variables which don't appear in the model). In bugsData, pass "format" to formatC as well as "digits" BugsHelper.c compiles cleanly with -Wall Correct date in DESCRIPTION Modified Paths: -------------- branches/linux/BRugs/DESCRIPTION branches/linux/BRugs/R/bugs.data.R branches/linux/BRugs/R/formatdata.R branches/linux/BRugs/inst/README-inst_OpenBUGS branches/linux/BRugs/man/bugs.data.Rd branches/linux/BRugs/src/BugsHelper.c Modified: branches/linux/BRugs/DESCRIPTION =================================================================== --- branches/linux/BRugs/DESCRIPTION 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/DESCRIPTION 2010-11-04 21:47:27 UTC (rev 176) @@ -1,7 +1,7 @@ Package: BRugs Title: OpenBUGS and its R / S-PLUS interface BRugs -Version: 0.6-0 -Date: 2010-04-30 +Version: 0.6-1 +Date: 2010-11-03 Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R Code modified, extended and packaged for R by Uwe Ligges and Sibylle Sturtz. Some ideas taken from the R2WinBUGS package based on code by Andrew Gelman. With considerable contributions by Gregor Gorjanc. Linux port of BRugs and other developments by Chris Jackson. Description: An R / S-PLUS package containing OpenBUGS and its R / S-PLUS interface BRugs. Maintainer: Uwe Ligges <li...@st...> Modified: branches/linux/BRugs/R/bugs.data.R =================================================================== --- branches/linux/BRugs/R/bugs.data.R 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/R/bugs.data.R 2010-11-04 21:47:27 UTC (rev 176) @@ -1,8 +1,8 @@ "bugsData" <- -function(data, fileName = file.path(tempdir(), "data.txt"), digits = 5){ +function(data, fileName = file.path(tempdir(), "data.txt"), format="E", digits = 5){ if(is.numeric(unlist(data))) if(is.R()) { - write.datafile(lapply(data, formatC, digits = digits, format = "E"), fileName) + write.datafile(lapply(data, formatC, digits = digits, format = format), fileName) } else { writeDatafileS4(data, towhere = "data.txt") @@ -11,7 +11,7 @@ if(is.R()) { data.list <- lapply(as.list(data), get, pos = parent.frame(2)) names(data.list) <- as.list(data) - write.datafile(lapply(data.list, formatC, digits = digits, format = "E"), fileName) + write.datafile(lapply(data.list, formatC, digits = digits, format = format), fileName) } else { data.list <- lapply(as.list(data), get, where = parent.frame(2)) Modified: branches/linux/BRugs/R/formatdata.R =================================================================== --- branches/linux/BRugs/R/formatdata.R 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/R/formatdata.R 2010-11-04 21:47:27 UTC (rev 176) @@ -1,28 +1,29 @@ "formatdata" <- function (datalist){ - if (!is.list(datalist) || is.data.frame(datalist)) + if (!is.list(datalist) || is.data.frame(datalist)) stop("argument to formatdata() ", "must be a list") n <- length(datalist) datalist.string <- vector(n, mode = "list") datanames <- names(datalist) for (i in 1:n) { - datalist.string[[i]] <- - switch(as.character(dimensions(datanames[i])), - "0" = paste(names(datalist)[i], - "=", as.character(datalist[[i]]), sep = ""), - "1" = paste(names(datalist)[i], - "=c(", paste(as.character(datalist[[i]]), collapse = ", "), - ")", sep = ""), - paste(names(datalist)[i], - "= structure(.Data= c(", - paste(as.character(as.vector(aperm(datalist[[i]]))), collapse = ", "), - "), .Dim=c(", - paste(as.character(dim(datalist[[i]])), collapse = ", "), - "))", sep = "") - ) + datalist.string[[i]] <- + if (length(datalist[[i]]) == 1) + paste(names(datalist)[i], + "=", as.character(datalist[[i]]), sep = "") + else if (is.vector(datalist[[i]]) && length(datalist[[i]]) > 1) + paste(names(datalist)[i], + "=c(", paste(as.character(datalist[[i]]), collapse = ", "), + ")", sep = "") + else + paste(names(datalist)[i], + "= structure(.Data= c(", + paste(as.character(as.vector(aperm(datalist[[i]]))), collapse = ", "), + "), .Dim=c(", + paste(as.character(dim(datalist[[i]])), collapse = ", "), + "))", sep = "") } - datalist.tofile <- paste("list(", - paste(unlist(datalist.string), collapse = ", "), + datalist.tofile <- paste("list(", + paste(unlist(datalist.string), collapse = ", "), ")", sep = "") return(datalist.tofile) } Modified: branches/linux/BRugs/inst/README-inst_OpenBUGS =================================================================== --- branches/linux/BRugs/inst/README-inst_OpenBUGS 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/inst/README-inst_OpenBUGS 2010-11-04 21:47:27 UTC (rev 176) @@ -13,8 +13,13 @@ REM OpenBUGS/Manuals/*.bmp REM OpenBUGS/Manuals/*.html +REM Run this script from Windows command prompt from within this directory as follows: +REM +REM cmd < README-inst_OpenBUGS +REM + REM Set the directory path of latest OpenBUGS distribution -set OpenBUGS=C:/Programs/BUGS/OpenBUGS_latest +set OpenBUGS="C:/Program Files/OpenBUGS/OpenBUGS312" REM Cleanup previous files and create the directory structure rm -Rf OpenBUGS @@ -25,7 +30,7 @@ REM Copy the files cp -f %OpenBUGS%/libOpenBUGS.dll . cp -f %OpenBUGS%/libOpenBUGS.so . -cp -f %OpenBUGS%/libtaucs.dll . +REM cp -f %OpenBUGS%/libtaucs.dll . cp -f %OpenBUGS%/Examples/{*.bmp,*.html,*.txt} Examples/. cp -f %OpenBUGS%/Developer/{*.bmp,*.html} Developer/. -cp -f %OpenBUGS%/Manuals/{*.bmp,*.html} Manuals/. \ No newline at end of file +cp -f %OpenBUGS%/Manuals/{*.bmp,*.html} Manuals/. Modified: branches/linux/BRugs/man/bugs.data.Rd =================================================================== --- branches/linux/BRugs/man/bugs.data.Rd 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/man/bugs.data.Rd 2010-11-04 21:47:27 UTC (rev 176) @@ -6,17 +6,20 @@ bugsData(data, fileName = file.path(tempdir(), "data.txt"), digits = 5) } \arguments{ - \item{data}{either a named list (names corresponding to variable names in the model file) + \item{data}{Either a named list (names corresponding to variable names in the model file) of the data for the OpenBUGS model, \emph{or} a vector or list of the names of the data objects used by the model} - \item{fileName}{the filename, defaults to \file{data.txt} in the temporary directory of the current R session} - \item{digits}{number of significant digits used for OpenBUGS input, see \code{\link{formatC}}} + \item{fileName}{The filename, defaults to \file{data.txt} in the temporary directory of the current R session} + \item{format}{String to pass to + \code{\link{formatC}} which controls formatting of numbers. The default \code{"E"} formats all numbers in + scientific notation. The alternative "fg" uses a standard format. } + \item{digits}{Number of significant digits used for OpenBUGS input, + see \code{\link{formatC}}. This may need to be adjusted from the + default of 5, for example when writing large integers.} } \value{ Invisibly returns the \code{fileName}. } -\note{\code{bugsData} uses \code{format="E"} internally, i.e. you need to - pay attention when writing integers containg many significant digits to the data file.} \seealso{\code{\link{BRugs}}} \keyword{file} \concept{data} Modified: branches/linux/BRugs/src/BugsHelper.c =================================================================== --- branches/linux/BRugs/src/BugsHelper.c 2010-10-02 13:00:50 UTC (rev 175) +++ branches/linux/BRugs/src/BugsHelper.c 2010-11-04 21:47:27 UTC (rev 176) @@ -104,9 +104,6 @@ free(fname); } -int file_size() { -} - void read_input_char(char *tmpdir, char **out, int *len, int cmdno) { char *fname; struct stat buf; @@ -174,7 +171,7 @@ free(fname); } -int do_TempDir(char *dir) { +void do_TempDir(char *dir) { int length; length = strlen(dir); SetTempDir(&dir, &length); @@ -205,7 +202,6 @@ int do_CharArray(char *cmd, char *tmpdir, int cmdno) { int length, outlength, res; char *out; - int i; length = strlen(cmd); read_input_char(tmpdir, &out, &outlength, cmdno); #ifdef DEBUG @@ -218,7 +214,7 @@ } int do_RealArray(char *cmd, char *tmpdir, int cmdno) { - int length, outlength, res, i; + int length, outlength, res; double *out; read_input_real(tmpdir, &out, &outlength, cmdno); length = strlen(cmd); @@ -234,7 +230,7 @@ } int do_Internalize(char *tmpdir, char *extfile){ - char *extpath, *extpath_base, *int_cmd; + char *extpath, *int_cmd; struct stat buf; int res; extpath = (char *) malloc(strlen(tmpdir) + 2 + strlen(extfile)); This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <chr...@us...> - 2011-03-07 15:09:21
|
Revision: 180 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=180&view=rev Author: chris-jackson Date: 2011-03-07 15:09:12 +0000 (Mon, 07 Mar 2011) Log Message: ----------- Changes to allow BRugs to work seamlessly with an existing installation of OpenBUGS on Linux and Windows. Requires OpenBUGS 3.2.1 or later. Modified Paths: -------------- branches/linux/BRugs/.Rbuildignore branches/linux/BRugs/DESCRIPTION branches/linux/BRugs/NEWS branches/linux/BRugs/R/bugs.data.R branches/linux/BRugs/R/formatdata.R branches/linux/BRugs/R/internal.R branches/linux/BRugs/R/samples.density.R branches/linux/BRugs/R/unix/help.R branches/linux/BRugs/R/windows/help.R branches/linux/BRugs/R/zzz.R branches/linux/BRugs/man/BRugs.Rd branches/linux/BRugs/man/BRugsFit.Rd branches/linux/BRugs/man/bugs.data.Rd branches/linux/BRugs/src/BugsHelper.c branches/linux/BRugs/src/Makevars branches/linux/BRugs/tests/BRugs.R branches/linux/BRugs/tests/examples.R branches/linux/BRugs/tests/functions.R Added Paths: ----------- branches/linux/BRugs/Changelog branches/linux/BRugs/R/unix/internal.R branches/linux/BRugs/R/unix/zzz.R branches/linux/BRugs/R/unix/zzz.R.in branches/linux/BRugs/R/windows/internal.R branches/linux/BRugs/R/windows/zzz.R branches/linux/BRugs/configure branches/linux/BRugs/configure.ac branches/linux/BRugs/configure.win branches/linux/BRugs/src/Makefile.win branches/linux/BRugs/src/Makevars.in Removed Paths: ------------- branches/linux/BRugs/R/internal-linux.R branches/linux/BRugs/R/internal-win.R branches/linux/BRugs/inst/README-inst_OpenBUGS branches/linux/BRugs/src/Makevars.win Modified: branches/linux/BRugs/.Rbuildignore =================================================================== --- branches/linux/BRugs/.Rbuildignore 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/.Rbuildignore 2011-03-07 15:09:12 UTC (rev 180) @@ -1,2 +1,3 @@ -inst/README-inst_OpenBUGS exec/BugsHelper +exec +.+\.Rout Added: branches/linux/BRugs/Changelog =================================================================== --- branches/linux/BRugs/Changelog (rev 0) +++ branches/linux/BRugs/Changelog 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1 @@ +See "NEWS" Modified: branches/linux/BRugs/DESCRIPTION =================================================================== --- branches/linux/BRugs/DESCRIPTION 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/DESCRIPTION 2011-03-07 15:09:12 UTC (rev 180) @@ -1,11 +1,12 @@ Package: BRugs -Title: OpenBUGS and its R / S-PLUS interface BRugs -Version: 0.6-1 -Date: 2010-11-03 -Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R Code modified, extended and packaged for R by Uwe Ligges and Sibylle Sturtz. Some ideas taken from the R2WinBUGS package based on code by Andrew Gelman. With considerable contributions by Gregor Gorjanc. Linux port of BRugs and other developments by Chris Jackson. -Description: An R / S-PLUS package containing OpenBUGS and its R / S-PLUS interface BRugs. -Maintainer: Uwe Ligges <li...@st...> -Depends: R (>= 2.5.0), coda +Title: R interface to the OpenBUGS MCMC software +Version: 0.7 +Date: 2011-03-07 +Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R interface developed by Uwe Ligges, Sibylle Sturtz, Andrew Gelman, Gregor Gorjanc and Chris Jackson. Linux port and most recent developments by Chris Jackson. +Description: Fully-interactive R interface to the OpenBUGS software for Bayesian analysis using MCMC sampling +Maintainer: Chris Jackson <chr...@mr...> +Depends: R (>= 2.5.0), utils, coda +SystemRequirements: OpenBUGS (>= 3.2.1) Archs: i386 License: GPL-2 URL: http://www.openbugs.info/ Modified: branches/linux/BRugs/NEWS =================================================================== --- branches/linux/BRugs/NEWS 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/NEWS 2011-03-07 15:09:12 UTC (rev 180) @@ -1,3 +1,38 @@ +Version 0.7 +----------- + +BRugs now works with an existing installation of OpenBUGS (3.2.1 or +later) instead of being distributed with the OpenBUGS library. + +On Windows, the OpenBUGS location is determined by a registry key +which is installed by the OpenBUGS for Windows installation program. + +On Linux, the OpenBUGS shared library and documentation are assumed to +be installed together in a library directory. Using the new OpenBUGS +for Linux source package OpenBUGS-3.2.1.tar.gz or later, this library +directory is by default + +/usr/local/lib/OpenBUGS + +In most cases it should be detected automatically when installing, but +it can be changed by running, for instance + +R CMD INSTALL --configure-args='--with-openbugs=/usr/lib/OpenBUGS' + + + +Version 0.61 +------------ +Fix for crash in bugsData + + +Version 0.6 +----------- + +Forked from the version of BRugs (0.5.3) available on CRAN Extras. +This new version supports Linux for the first time, as detailed below. + + CHANGES MADE FOR LINUX PORT OF BRugs * A C program called BugsHelper is used to call the OpenBUGS shared Modified: branches/linux/BRugs/R/bugs.data.R =================================================================== --- branches/linux/BRugs/R/bugs.data.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/bugs.data.R 2011-03-07 15:09:12 UTC (rev 180) @@ -1,12 +1,14 @@ "bugsData" <- function(data, fileName = file.path(tempdir(), "data.txt"), format="E", digits = 5){ - if(is.numeric(unlist(data))) + if(is.list(data)) { + data <- lapply(data, function(x){x <- if(is.character(x)||is.factor(x)) match(x, unique(x)) else x}) if(is.R()) { write.datafile(lapply(data, formatC, digits = digits, format = format), fileName) } else { writeDatafileS4(data, towhere = "data.txt") } + } else { if(is.R()) { data.list <- lapply(as.list(data), get, pos = parent.frame(2)) Modified: branches/linux/BRugs/R/formatdata.R =================================================================== --- branches/linux/BRugs/R/formatdata.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/formatdata.R 2011-03-07 15:09:12 UTC (rev 180) @@ -6,7 +6,9 @@ datalist.string <- vector(n, mode = "list") datanames <- names(datalist) for (i in 1:n) { - datalist.string[[i]] <- + if (is.factor(datalist[[i]])) + datalist[[i]] <- as.integer(datalist[[i]]) + datalist.string[[i]] <- if (length(datalist[[i]]) == 1) paste(names(datalist)[i], "=", as.character(datalist[[i]]), sep = "") Deleted: branches/linux/BRugs/R/internal-linux.R =================================================================== --- branches/linux/BRugs/R/internal-linux.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/internal-linux.R 2011-03-07 15:09:12 UTC (rev 180) @@ -1,36 +0,0 @@ -dquote <- function(x){ - paste("\"", x, "\"", sep="") -} - -.OpenBUGS.Linux <- function(cmds, cmdtypes, args) -{ - ncmds <- length(cmds) - if (ncmds > 99999) stop("Maximum number of OpenBUGS API commands exceeded") - tempDir <- getOption("BRugsTmpdir") - ## Don't want internalize/externalize to overwrite the command - ## output buffer, so redirect its output to a separate trash can. - trashDir <- paste(tempDir, "_trash", sep="") - extFile <- getOption("BRugsExtFile") - pkgPath <- searchpaths()[search()=="package:BRugs"] - bugsPath <- paste(pkgPath, "/exec/BugsHelper", sep="") - shcmd <- paste(bugsPath, dquote(tempDir), dquote(trashDir), dquote(extFile)) - for (i in 1:ncmds) { - if (cmdtypes[i] %in% c("CharArray","RealArray")) - cat(args[[i]], file=paste(tempDir, "/input",i,".txt", sep="")) - cmdtype <- match(cmdtypes[i], .OpenBUGS.cmdtypes) - 1 - shcmd <- paste(shcmd, dquote(cmds[i]), cmdtype) - } - res <- system(shcmd) - handleRes(res) - out <- vector(ncmds, mode="list") - for (i in 1:ncmds) { - if (cmdtypes[i] %in% c("Integer","CharArray","RealArray")) - out[[i]] <- scan(paste(tempDir,"/output",i,".txt",sep=""), - switch(cmdtypes[i], - "Integer" = integer(), - "CharArray" = character(), - "RealArray" = double()), - quiet=TRUE) - } - out -} Deleted: branches/linux/BRugs/R/internal-win.R =================================================================== --- branches/linux/BRugs/R/internal-win.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/internal-win.R 2011-03-07 15:09:12 UTC (rev 180) @@ -1,33 +0,0 @@ -### Run a list of OpenBUGS API command strings - -.OpenBUGS.Windows <- function(cmds, cmdtypes, args) -{ - ncmds <- length(cmds) - out <- vector(ncmds, mode="list") - for (i in 1:ncmds) { - out[[i]] <- switch(cmdtypes[i], - "CmdInterpreter" = { - res <- .C("CmdInterpreter", cmds[i], nchar(cmds[i]), integer(1), PACKAGE = "BRugs") - handleRes(res[[3]]) - res - }, - "Integer" = { - values <- .C("Integer", cmds[i], nchar(cmds[i]), integer(1), integer(1), PACKAGE = "BRugs") - handleRes(values[[4]]) - as.integer(values[[3]]) - }, - "CharArray" = { - values <- .C("CharArray", cmds[i], nchar(cmds[i]), args[[i]], nchar(args[[i]]), integer(1), PACKAGE="BRugs") - handleRes(values[[5]]) - values[[3]] - }, - "RealArray" = { - values <- .C("RealArray", cmds[i], nchar(cmds[i]), args[[i]], length(args[[i]]), integer(1), PACKAGE="BRugs") - handleRes(values[[5]]) - values[[3]] - }) - - } - out -} - Modified: branches/linux/BRugs/R/internal.R =================================================================== --- branches/linux/BRugs/R/internal.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/internal.R 2011-03-07 15:09:12 UTC (rev 180) @@ -29,10 +29,7 @@ if (is.null(args)) args <- as.list(rep(NA, ncmds)) stopifnot(ncmds==length(cmdtypes)) stopifnot(ncmds==length(args)) - switch(Sys.info()["sysname"], - "Linux" = .OpenBUGS.Linux(cmds, cmdtypes, args), - "Windows" = .OpenBUGS.Windows(cmds, cmdtypes, args), - stop("Only Linux and Windows are supported")) + .OpenBUGS.platform(cmds, cmdtypes, args) } handleRes <- function(res) Modified: branches/linux/BRugs/R/samples.density.R =================================================================== --- branches/linux/BRugs/R/samples.density.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/samples.density.R 2011-03-07 15:09:12 UTC (rev 180) @@ -31,10 +31,12 @@ thin <- max(c(thin, 1)) samplesSetThin(thin) mons <- samplesMonitors(node) - if (is.R()) - par(mfrow = mfrow, ask = ask, ann = ann) - else - par(mfrow = mfrow, ask = ask) + if (plot) { + if (is.R()) + par(mfrow = mfrow, ask = ask, ann = ann) + else + par(mfrow = mfrow, ask = ask) + } result <- sapply(mons, plotDensity, plot=plot, ...) if (!is.R()) invisible() Modified: branches/linux/BRugs/R/unix/help.R =================================================================== --- branches/linux/BRugs/R/unix/help.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/unix/help.R 2011-03-07 15:09:12 UTC (rev 180) @@ -24,6 +24,6 @@ "switch to its window."), exdent = 4)) writeLines("Otherwise, be patient ...") - browseURL(system.file("OpenBUGS", "Manuals", "Contents.html", package="BRugs")) + browseURL(paste(options()$OpenBUGS, "doc", "Manuals", "Contents.html", sep="/")) invisible("") } Added: branches/linux/BRugs/R/unix/internal.R =================================================================== --- branches/linux/BRugs/R/unix/internal.R (rev 0) +++ branches/linux/BRugs/R/unix/internal.R 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,36 @@ +dquote <- function(x){ + paste("\"", x, "\"", sep="") +} + +.OpenBUGS.platform <- function(cmds, cmdtypes, args) +{ + ncmds <- length(cmds) + if (ncmds > 99999) stop("Maximum number of OpenBUGS API commands exceeded") + tempDir <- getOption("BRugsTmpdir") + ## Don't want internalize/externalize to overwrite the command + ## output buffer, so redirect its output to a separate trash can. + trashDir <- paste(tempDir, "_trash", sep="") + extFile <- getOption("BRugsExtFile") + pkgPath <- searchpaths()[search()=="package:BRugs"] + bugsPath <- paste(pkgPath, "/exec/BugsHelper", sep="") + shcmd <- paste(bugsPath, dquote(tempDir), dquote(trashDir), dquote(extFile)) + for (i in 1:ncmds) { + if (cmdtypes[i] %in% c("CharArray","RealArray")) + cat(args[[i]], file=paste(tempDir, "/input",i,".txt", sep="")) + cmdtype <- match(cmdtypes[i], .OpenBUGS.cmdtypes) - 1 + shcmd <- paste(shcmd, dquote(cmds[i]), cmdtype) + } + res <- system(shcmd) + handleRes(res) + out <- vector(ncmds, mode="list") + for (i in 1:ncmds) { + if (cmdtypes[i] %in% c("Integer","CharArray","RealArray")) + out[[i]] <- scan(paste(tempDir,"/output",i,".txt",sep=""), + switch(cmdtypes[i], + "Integer" = integer(), + "CharArray" = character(), + "RealArray" = double()), + quiet=TRUE) + } + out +} Added: branches/linux/BRugs/R/unix/zzz.R =================================================================== --- branches/linux/BRugs/R/unix/zzz.R (rev 0) +++ branches/linux/BRugs/R/unix/zzz.R 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,18 @@ +if (is.R()){ + + ".onLoad" <- function(lib, pkg){ + ## TODO any need for these to be user specifiable? + options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) + options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) + options(OpenBUGS = "/home/chris/usr/lib/OpenBUGS") + + if(is.null(getOption("BRugsVerbose"))) + options("BRugsVerbose" = TRUE) + .initGlobals() + options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) + } + + ".onUnload" <- function(libpath){ + } + +} Added: branches/linux/BRugs/R/unix/zzz.R.in =================================================================== --- branches/linux/BRugs/R/unix/zzz.R.in (rev 0) +++ branches/linux/BRugs/R/unix/zzz.R.in 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,18 @@ +if (is.R()){ + + ".onLoad" <- function(lib, pkg){ + ## TODO any need for these to be user specifiable? + options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) + options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) + options(OpenBUGS = "@OPENBUGS@") + + if(is.null(getOption("BRugsVerbose"))) + options("BRugsVerbose" = TRUE) + .initGlobals() + options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) + } + + ".onUnload" <- function(libpath){ + } + +} Modified: branches/linux/BRugs/R/windows/help.R =================================================================== --- branches/linux/BRugs/R/windows/help.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/windows/help.R 2011-03-07 15:09:12 UTC (rev 180) @@ -2,7 +2,7 @@ { ## stolen from help.start() # a <- system.file("OpenBUGS", "Manuals", "WinBUGS Manual.html", package="BRugs") - # if (!file.exists(a)) + # if (!file.exists(a)) # stop("I can't find the html help") # a <- chartr("/", "\\", a) # message("If nothing happens, you should open `", a, "' yourself") @@ -15,9 +15,9 @@ help.WinBUGS <- function(browser = getOption("browser")) { # stolen from help.start() - a <- system.file("OpenBUGS", "Manuals", "Contents.html", package="BRugs") - if (!file.exists(a)) - stop("I can't find the html help") + a <- paste(options()$OpenBUGS, "Manuals", "Contents.html", sep="\\") + if (!file.exists(a)) + stop("HTML help not found in file ", a) if (is.R()) a <- chartr("/", "\\", a) else Added: branches/linux/BRugs/R/windows/internal.R =================================================================== --- branches/linux/BRugs/R/windows/internal.R (rev 0) +++ branches/linux/BRugs/R/windows/internal.R 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,32 @@ +### Run a list of OpenBUGS API command strings + +.OpenBUGS.platform <- function(cmds, cmdtypes, args) +{ + ncmds <- length(cmds) + out <- vector(ncmds, mode="list") + for (i in 1:ncmds) { + out[[i]] <- switch(cmdtypes[i], + "CmdInterpreter" = { + res <- .C("CmdInterpreter", cmds[i], nchar(cmds[i]), integer(1), PACKAGE="libOpenBUGS") + handleRes(res[[3]]) + res + }, + "Integer" = { + values <- .C("Integer", cmds[i], nchar(cmds[i]), integer(1), integer(1), PACKAGE="libOpenBUGS") + handleRes(values[[4]]) + as.integer(values[[3]]) + }, + "CharArray" = { + values <- .C("CharArray", cmds[i], nchar(cmds[i]), args[[i]], nchar(args[[i]]), integer(1), PACKAGE="libOpenBUGS") + handleRes(values[[5]]) + values[[3]] + }, + "RealArray" = { + values <- .C("RealArray", cmds[i], nchar(cmds[i]), args[[i]], length(args[[i]]), integer(1), PACKAGE="libOpenBUGS") + handleRes(values[[5]]) + values[[3]] + }) + + } + out +} Added: branches/linux/BRugs/R/windows/zzz.R =================================================================== --- branches/linux/BRugs/R/windows/zzz.R (rev 0) +++ branches/linux/BRugs/R/windows/zzz.R 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,44 @@ +if (is.R()){ + + ".onLoad" <- function(lib, pkg){ + ob.reg <- try(utils:::readRegistry("Software\\OpenBUGS","HLM")) + if (inherits(ob.reg, "try-error")) stop("OpenBUGS 3.2.1 or greater must be installed") + rnames <- names(ob.reg) + ver <- gsub("OpenBUGS ", "", rnames) + ver <- gsub("(.+)e$","\\1", ver) + version.inst <- as.numeric(paste(substr(ver, 1, 2), gsub("\\.","",substr(ver, 3, nchar(ver))), sep="")) + deps <- utils:::packageDescription("BRugs", fields="SystemRequirements") + ver <- gsub(".*OpenBUGS ?\\(>= ?(.+)\\).*", "\\1", deps) + version.req <- as.numeric(paste(substr(ver, 1, 2), gsub("\\.","",substr(ver, 3, nchar(ver))), sep="")) + if (max(version.inst) < version.req) + stop("Found OpenBUGS version ", version.inst, ". Requires ", version.req, " or greater") + ## OpenBUGS installation location + options(OpenBUGS = utils:::readRegistry(paste("Software","OpenBUGS",rnames[which.max(version.inst)],sep="\\"),"HLM")$InstallPath) + libname <- paste(options()$OpenBUGS, "libOpenBUGS.dll", sep="/") + if (!file.exists(libname)) { + stop("Shared library \"libOpenBUGS.dll\" not found in ", options()$OpenBUGS) + } + ## All checks passed - load the DLL + dyn.load(libname) + len <- nchar(options()$OpenBUGS) + .C("SetWorkingDir", as.character(options()$OpenBUGS), len, PACKAGE="libOpenBUGS") + ## Set temporary dir for "buffer.txt" output + tempDir <- gsub("\\\\", "/", tempdir()) + .C("SetTempDir", as.character(tempDir), nchar(tempDir), PACKAGE="libOpenBUGS") + command <- "BugsMappers.SetDest(2)" + .CmdInterpreter(command) + + if(is.null(getOption("BRugsVerbose"))) + options("BRugsVerbose" = TRUE) + .initGlobals() + options(OpenBUGSExamples = paste(options()$OpenBUGS, "Examples", sep="/")) + } + + ".onUnload" <- function(libpath){ + if(is.loaded("CmdInterpreter")) { + libname <- paste(options()$OpenBUGS, "libOpenBUGS.dll", sep="/") + dyn.unload(libname) + } + } + +} Modified: branches/linux/BRugs/R/zzz.R =================================================================== --- branches/linux/BRugs/R/zzz.R 2010-11-13 17:31:25 UTC (rev 179) +++ branches/linux/BRugs/R/zzz.R 2011-03-07 15:09:12 UTC (rev 180) @@ -1,3 +1,5 @@ +## See unix/zzz.R, windows/zzz.R for platform specific .onLoad functions + if (is.R()){ .initGlobals <- function(){ @@ -7,61 +9,19 @@ options("BRugsSamplesLastChain" = 1) options("BRugsSamplesThin" = 1) options("BRugsSamplesVariable" = "*") - options("BRugsNextChain" = 1) # index of chain which needs to be initialized next + options("BRugsNextChain" = 1) # index of chain which needs to be initialized next options("BRugsPrec" = 4) } - - .onLoad <- function(...) { - switch(Sys.info()["sysname"], - "Linux" = .onLoad.Linux(...), - "Windows" = .onLoad.Windows(...), - stop("Only Linux and Windows are supported")) - if(is.null(getOption("BRugsVerbose"))) - options("BRugsVerbose" = TRUE) - .initGlobals() - } - - ".onLoad.Windows" <- function(lib, pkg){ - ## sets path / file variables and initializes subsystems - root <- file.path(system.file("OpenBUGS", package=pkg)) - library.dynam("BRugs", pkg, lib) - len <- nchar(root) - tempDir <- gsub("\\\\", "/", tempdir()) - .C("SetWorkingDir", as.character(root), len, PACKAGE="BRugs") - .C("SetTempDir", as.character(tempDir), nchar(tempDir), PACKAGE="BRugs") - command <- "BugsMappers.SetDest(2)" - .CmdInterpreter(command) - } - ".onLoad.Linux" <- function(lib, pkg){ - ## TODO any need for these to be user specifiable? - options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) - options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) - } - ".onAttach" <- function(lib, pkg){ message("Welcome to BRugs running on OpenBUGS version 3.1.2") } - .onUnload <- function(...) { - switch(Sys.info()["sysname"], - "Linux" = .onUnload.Linux(...), - "Windows" = .onUnload.Windows(...), - stop("Only Linux and Windows are supported")) - } - - ".onUnload.Windows" <- function(libpath){ - library.dynam.unload("BRugs", libpath) - } - - ".onUnload.Linux" <- function(libpath){ - } - ## Overwriting new (from R-2.6.0) sQuote (for typing human readable text) in R within the BRugs Namespace! ## we cannot use sQuote that uses fancy quotes! sQuote <- function(x) paste("'", x, "'", sep="") - + } else { # ends if (is.R()) ".First.lib" <- function(lib.loc, section) @@ -76,12 +36,12 @@ command <- "BugsMappers.SetDest(2)" .C("CmdInterpreter", as.character(command), nchar(command), integer(1)) if(is.null(getOption("BRugsVerbose"))) - options("BRugsVerbose" = TRUE) + options("BRugsVerbose" = TRUE) invisible() } - + .tempDir <- getwd() - + tempdir <- function(){ .tempDir } } # ends else Added: branches/linux/BRugs/configure =================================================================== --- branches/linux/BRugs/configure (rev 0) +++ branches/linux/BRugs/configure 2011-03-07 15:09:12 UTC (rev 180) @@ -0,0 +1,5000 @@ +#! /bin/sh +# Guess values for system-dependent variables and create Makefiles. +# Generated by GNU Autoconf 2.65 for BRugs 0.7. +# +# +# Copyright (C) 1992, 1993, 1994, 1995, 1996, 1998, 1999, 2000, 2001, +# 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009 Free Software Foundation, +# Inc. +# +# +# This configure script is free software; the Free Software Foundation +# gives unlimited permission to copy, distribute and modify it. +## -------------------- ## +## M4sh Initialization. ## +## -------------------- ## + +# Be more Bourne compatible +DUALCASE=1; export DUALCASE # for MKS sh +if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : + emulate sh + NULLCMD=: + # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which + # is contrary to our usage. Disable this feature. + alias -g '${1+"$@"}'='"$@"' + setopt NO_GLOB_SUBST +else + case `(set -o) 2>/dev/null` in #( + *posix*) : + set -o posix ;; #( + *) : + ;; +esac +fi + + +as_nl=' +' +export as_nl +# Printing a long string crashes Solaris 7 /usr/bin/printf. +as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' +as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo +as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo +# Prefer a ksh shell builtin over an external printf program on Solaris, +# but without wasting forks for bash or zsh. +if test -z "$BASH_VERSION$ZSH_VERSION" \ + && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then + as_echo='print -r --' + as_echo_n='print -rn --' +elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then + as_echo='printf %s\n' + as_echo_n='printf %s' +else + if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then + as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' + as_echo_n='/usr/ucb/echo -n' + else + as_echo_body='eval expr "X$1" : "X\\(.*\\)"' + as_echo_n_body='eval + arg=$1; + case $arg in #( + *"$as_nl"*) + expr "X$arg" : "X\\(.*\\)$as_nl"; + arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; + esac; + expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" + ' + export as_echo_n_body + as_echo_n='sh -c $as_echo_n_body as_echo' + fi + export as_echo_body + as_echo='sh -c $as_echo_body as_echo' +fi + +# The user is always right. +if test "${PATH_SEPARATOR+set}" != set; then + PATH_SEPARATOR=: + (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { + (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || + PATH_SEPARATOR=';' + } +fi + + +# IFS +# We need space, tab and new line, in precisely that order. Quoting is +# there to prevent editors from complaining about space-tab. +# (If _AS_PATH_WALK were called with IFS unset, it would disable word +# splitting by setting IFS to empty value.) +IFS=" "" $as_nl" + +# Find who we are. Look in the path if we contain no directory separator. +case $0 in #(( + *[\\/]* ) as_myself=$0 ;; + *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR +for as_dir in $PATH +do + IFS=$as_save_IFS + test -z "$as_dir" && as_dir=. + test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break + done +IFS=$as_save_IFS + + ;; +esac +# We did not find ourselves, most probably we were run as `sh COMMAND' +# in which case we are not to be found in the path. +if test "x$as_myself" = x; then + as_myself=$0 +fi +if test ! -f "$as_myself"; then + $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 + exit 1 +fi + +# Unset variables that we do not need and which cause bugs (e.g. in +# pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" +# suppresses any "Segmentation fault" message there. '((' could +# trigger a bug in pdksh 5.2.14. +for as_var in BASH_ENV ENV MAIL MAILPATH +do eval test x\${$as_var+set} = xset \ + && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : +done +PS1='$ ' +PS2='> ' +PS4='+ ' + +# NLS nuisances. +LC_ALL=C +export LC_ALL +LANGUAGE=C +export LANGUAGE + +# CDPATH. +(unset CDPATH) >/dev/null 2>&1 && unset CDPATH + +if test "x$CONFIG_SHELL" = x; then + as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : + emulate sh + NULLCMD=: + # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which + # is contrary to our usage. Disable this feature. + alias -g '\${1+\"\$@\"}'='\"\$@\"' + setopt NO_GLOB_SUBST +else + case \`(set -o) 2>/dev/null\` in #( + *posix*) : + set -o posix ;; #( + *) : + ;; +esac +fi +" + as_required="as_fn_return () { (exit \$1); } +as_fn_success () { as_fn_return 0; } +as_fn_failure () { as_fn_return 1; } +as_fn_ret_success () { return 0; } +as_fn_ret_failure () { return 1; } + +exitcode=0 +as_fn_success || { exitcode=1; echo as_fn_success failed.; } +as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } +as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } +as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } +if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : + +else + exitcode=1; echo positional parameters were not saved. +fi +test x\$exitcode = x0 || exit 1" + as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO + as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO + eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && + test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1" + if (eval "$as_required") 2>/dev/null; then : + as_have_required=yes +else + as_have_required=no +fi + if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : + +else + as_save_IFS=$IFS; IFS=$PATH_SEPARATOR +as_found=false +for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH +do + IFS=$as_save_IFS + test -z "$as_dir" && as_dir=. + as_found=: + case $as_dir in #( + /*) + for as_base in sh bash ksh sh5; do + # Try only shells that exist, to save several forks. + as_shell=$as_dir/$as_base + if { test -f "$as_shell" || test -f "$as_shell.exe"; } && + { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : + CONFIG_SHELL=$as_shell as_have_required=yes + if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : + break 2 +fi +fi + done;; + esac + as_found=false +done +$as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && + { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : + CONFIG_SHELL=$SHELL as_have_required=yes +fi; } +IFS=$as_save_IFS + + + if test "x$CONFIG_SHELL" != x; then : + # We cannot yet assume a decent shell, so we have to provide a + # neutralization value for shells without unset; and this also + # works around shells that cannot unset nonexistent variables. + BASH_ENV=/dev/null + ENV=/dev/null + (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV + export CONFIG_SHELL + exec "$CONFIG_SHELL" "$as_myself" ${1+"$@"} +fi + + if test x$as_have_required = xno; then : + $as_echo "$0: This script requires a shell more modern than all" + $as_echo "$0: the shells that I found on your system." + if test x${ZSH_VERSION+set} = xset ; then + $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" + $as_echo "$0: be upgraded to zsh 4.3.4 or later." + else + $as_echo "$0: Please tell bug...@gn... about your system, +$0: including any error possibly output before this +$0: message. Then install a modern shell, or manually run +$0: the script under such a shell if you do have one." + fi + exit 1 +fi +fi +fi +SHELL=${CONFIG_SHELL-/bin/sh} +export SHELL +# Unset more variables known to interfere with behavior of common tools. +CLICOLOR_FORCE= GREP_OPTIONS= +unset CLICOLOR_FORCE GREP_OPTIONS + +## --------------------- ## +## M4sh Shell Functions. ## +## --------------------- ## +# as_fn_unset VAR +# --------------- +# Portably unset VAR. +as_fn_unset () +{ + { eval $1=; unset $1;} +} +as_unset=as_fn_unset + +# as_fn_set_status STATUS +# ----------------------- +# Set $? to STATUS, without forking. +as_fn_set_status () +{ + return $1 +} # as_fn_set_status + +# as_fn_exit STATUS +# ----------------- +# Exit the shell with STATUS, even in a "trap 0" or "set -e" context. +as_fn_exit () +{ + set +e + as_fn_set_status $1 + exit $1 +} # as_fn_exit + +# as_fn_mkdir_p +# ------------- +# Create "$as_dir" as a directory, including parents if necessary. +as_fn_mkdir_p () +{ + + case $as_dir in #( + -*) as_dir=./$as_dir;; + esac + test -d "$as_dir" || eval $as_mkdir_p || { + as_dirs= + while :; do + case $as_dir in #( + *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( + *) as_qdir=$as_dir;; + esac + as_dirs="'$as_qdir' $as_dirs" + as_dir=`$as_dirname -- "$as_dir" || +$as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ + X"$as_dir" : 'X\(//\)[^/]' \| \ + X"$as_dir" : 'X\(//\)$' \| \ + X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || +$as_echo X"$as_dir" | + sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ + s//\1/ + q + } + /^X\(\/\/\)[^/].*/{ + s//\1/ + q + } + /^X\(\/\/\)$/{ + s//\1/ + q + } + /^X\(\/\).*/{ + s//\1/ + q + } + s/.*/./; q'` + test -d "$as_dir" && break + done + test -z "$as_dirs" || eval "mkdir $as_dirs" + } || test -d "$as_dir" || as_fn_error "cannot create directory $as_dir" + + +} # as_fn_mkdir_p +# as_fn_append VAR VALUE +# ---------------------- +# Append the text in VALUE to the end of the definition contained in VAR. Take +# advantage of any shell optimizations that allow amortized linear growth over +# repeated appends, instead of the typical quadratic growth present in naive +# implementations. +if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : + eval 'as_fn_append () + { + eval $1+=\$2 + }' +else + as_fn_append () + { + eval $1=\$$1\$2 + } +fi # as_fn_append + +# as_fn_arith ARG... +# ------------------ +# Perform arithmetic evaluation on the ARGs, and store the result in the +# global $as_val. Take advantage of shells that can avoid forks. The arguments +# must be portable across $(()) and expr. +if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : + eval 'as_fn_arith () + { + as_val=$(( $* )) + }' +else + as_fn_arith () + { + as_val=`expr "$@" || test $? -eq 1` + } +fi # as_fn_arith + + +# as_fn_error ERROR [LINENO LOG_FD] +# --------------------------------- +# Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are +# provided, also output the error to LOG_FD, referencing LINENO. Then exit the +# script with status $?, using 1 if that was 0. +as_fn_error () +{ + as_status=$?; test $as_status -eq 0 && as_status=1 + if test "$3"; then + as_lineno=${as_lineno-"$2"} as_lineno_stack=as_lineno_stack=$as_lineno_stack + $as_echo "$as_me:${as_lineno-$LINENO}: error: $1" >&$3 + fi + $as_echo "$as_me: error: $1" >&2 + as_fn_exit $as_status +} # as_fn_error + +if expr a : '\(a\)' >/dev/null 2>&1 && + test "X`expr 00001 : '.*\(...\)'`" = X001; then + as_expr=expr +else + as_expr=false +fi + +if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then + as_basename=basename +else + as_basename=false +fi + +if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then + as_dirname=dirname +else + as_dirname=false +fi + +as_me=`$as_basename -- "$0" || +$as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ + X"$0" : 'X\(//\)$' \| \ + X"$0" : 'X\(/\)' \| . 2>/dev/null || +$as_echo X/"$0" | + sed '/^.*\/\([^/][^/]*\)\/*$/{ + s//\1/ + q + } + /^X\/\(\/\/\)$/{ + s//\1/ + q + } + /^X\/\(\/\).*/{ + s//\1/ + q + } + s/.*/./; q'` + +# Avoid depending upon Character Ranges. +as_cr_letters='abcdefghijklmnopqrstuvwxyz' +as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' +as_cr_Letters=$as_cr_letters$as_cr_LETTERS +as_cr_digits='0123456789' +as_cr_alnum=$as_cr_Letters$as_cr_digits + + + as_lineno_1=$LINENO as_lineno_1a=$LINENO + as_lineno_2=$LINENO as_lineno_2a=$LINENO + eval 'test "x$as_lineno_1'$as_run'" != "x$as_lineno_2'$as_run'" && + test "x`expr $as_lineno_1'$as_run' + 1`" = "x$as_lineno_2'$as_run'"' || { + # Blame Lee E. McMahon (1931-1989) for sed's syntax. :-) + sed -n ' + p + /[$]LINENO/= + ' <$as_myself | + sed ' + s/[$]LINENO.*/&-/ + t lineno + b + :lineno + N + :loop + s/[$]LINENO\([^'$as_cr_alnum'_].*\n\)\(.*\)/\2\1\2/ + t loop + s/-\n.*// + ' >$as_me.lineno && + chmod +x "$as_me.lineno" || + { $as_echo "$as_me: error: cannot create $as_me.lineno; rerun with a POSIX shell" >&2; as_fn_exit 1; } + + # Don't try to exec as it changes $[0], causing all sort of problems + # (the dirname of $[0] is not the place where we might find the + # original and so on. Autoconf is especially sensitive to this). + . "./$as_me.lineno" + # Exit status is that of the last command. + exit +} + +ECHO_C= ECHO_N= ECHO_T= +case `echo -n x` in #((((( +-n*) + case `echo 'xy\c'` in + *c*) ECHO_T=' ';; # ECHO_T is single tab character. + xy) ECHO_C='\c';; + *) echo `echo ksh88 bug on AIX 6.1` > /dev/null + ECHO_T=' ';; + esac;; +*) + ECHO_N='-n';; +esac + +rm -f conf$$ conf$$.exe conf$$.file +if test -d conf$$.dir; then + rm -f conf$$.dir/conf$$.file +else + rm -f conf$$.dir + mkdir conf$$.dir 2>/dev/null +fi +if (echo >conf$$.file) 2>/dev/null; then + if ln -s conf$$.file conf$$ 2>/dev/null; then + as_ln_s='ln -s' + # ... but there are two gotchas: + # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. + # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. + # In both cases, we have to default to `cp -p'. + ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || + as_ln_s='cp -p' + elif ln conf$$.file conf$$ 2>/dev/null; then + as_ln_s=ln + else + as_ln_s='cp -p' + fi +else + as_ln_s='cp -p' +fi +rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file +rmdir conf$$.dir 2>/dev/null + +if mkdir -p . 2>/dev/null; then + as_mkdir_p='mkdir -p "$as_dir"' +else + test -d ./-p && rmdir ./-p + as_mkdir_p=false +fi + +if test -x / >/dev/null 2>&1; then + as_test_x='test -x' +else + if ls -dL / >/dev/null 2>&1; then + as_ls_L_option=L + else + as_ls_L_option= + fi + as_test_x=' + eval sh -c '\'' + if test -d "$1"; then + test -d "$1/."; + else + case $1 in #( + -*)set "./$1";; + esac; + case `ls -ld'$as_ls_L_option' "$1" 2>/dev/null` in #(( + ???[sx]*):;;*)false;;esac;fi + '\'' sh + ' +fi +as_executable_p=$as_test_x + +# Sed expression to map a string onto a valid CPP name. +as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" + +# Sed expression to map a string onto a valid variable name. +as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" + + +test -n "$DJDIR" || exec 7<&0 </dev/null +exec 6>&1 + +# Name of the host. +# hostname on some systems (SVR3.2, Linux) returns a bogus exit status, +# so uname gets run too. +ac_hostname=`(hostname || uname -n) 2>/dev/null | sed 1q` + +# +# Initializations. +# +ac_default_prefix=/usr/local +ac_clean_files= +ac_config_libobj_dir=. +LIBOBJS= +cross_compiling=no +subdirs= +MFLAGS= +MAKEFLAGS= + +# Identity of this package. +PACKAGE_NAME='BRugs' +PACKAGE_TARNAME='brugs' +PACKAGE_VERSION='0.7' +PACKAGE_STRING='BRugs 0.7' +PACKAGE_BUGREPORT='' +PACKAGE_URL='' + +ac_default_prefix=/usr/local +ac_subst_vars='LTLIBOBJS +LIBOBJS +OPENBUGS +OBJEXT +EXEEXT +ac_ct_CC +CPPFLAGS +LDFLAGS +CFLAGS +CC +ac_prefix_program +target_alias +host_alias +build_alias +LIBS +ECHO_T +ECHO_N +ECHO_C +DEFS +mandir +localedir +libdir +psdir +pdfdir +dvidir +htmldir +infodir +docdir +oldincludedir +includedir +localstatedir +sharedstatedir +sysconfdir +datadir +datarootdir +libexecdir +sbindir +bindir +program_transform_name +prefix +exec_prefix +PACKAGE_URL +PACKAGE_BUGREPORT +PACKAGE_STRING +PACKAGE_VERSION +PACKAGE_TARNAME +PACKAGE_NAME +PATH_SEPARATOR +SHELL' +ac_subst_files='' +ac_user_opts=' +enable_option_checking +with_openbugs +' + ac_precious_vars='build_alias +host_alias +target_alias +CC +CFLAGS +LDFLAGS +LIBS +CPPFLAGS' + + +# Initialize some variables set by options. +ac_init_help= +ac_init_version=false +ac_unrecognized_opts= +ac_unrecognized_sep= +# The variables have the same names as the options, with +# dashes changed to underlines. +cache_file=/dev/null +exec_prefix=NONE +no_create= +no_recursion= +prefix=NONE +program_prefix=NONE +program_suffix=NONE +program_transform_name=s,x,x, +silent= +site= +srcdir= +verbose= +x_includes=NONE +x_libraries=NONE + +# Installation directory options. +# These are left unexpanded so users can "make install exec_prefix=/foo" +# and all the variables that are supposed to be based on exec_prefix +# by default will actually change. +# Use braces instead of parens because sh, perl, etc. also accept them. +# (The list follows the same order as the GNU Coding Standards.) +bindir='${exec_prefix}/bin' +sbindir='${exec_prefix}/sbin' +libexecdir='${exec_prefix}/libexec' +datarootdir='${prefix}/share' +datadir='${datarootdir}' +sysconfdir='${prefix}/etc' +sharedstatedir='${prefix}/com' +localstatedir='${prefix}/var' +includedir='${prefix}/include' +oldincludedir='/usr/include' +docdir='${datarootdir}/doc/${PACKAGE_TARNAME}' +infodir='${datarootdir}/info' +htmldir='${docdir}' +dvidir='${docdir}' +pdfdir='${docdir}' +psdir='${docdir}' +libdir='${exec_prefix}/lib' +localedir='${datarootdir}/locale' +mandir='${datarootdir}/man' + +ac_prev= +ac_dashdash= +for ac_option +do + # If the previous option needs an argument, assign it. + if test -n "$ac_prev"; then + eval $ac_prev=\$ac_option + ac_prev= + continue + fi + + case $ac_option in + *=*) ac_optarg=`expr "X$ac_option" : '[^=]*=\(.*\)'` ;; + *) ac_optarg=yes ;; + esac + + # Accept the important Cygnus configure options, so we can diagnose typos. + + case $ac_dashdash$ac_option in + --) + ac_dashdash=yes ;; + + -bindir | --bindir | --bindi | --bind | --bin | --bi) + ac_prev=bindir ;; + -bindir=* | --bindir=* | --bindi=* | --bind=* | --bin=* | --bi=*) + bindir=$ac_optarg ;; + + -build | --build | --buil | --bui | --bu) + ac_prev=build_alias ;; + -build=* | --build=* | --buil=* | --bui=* | --bu=*) + build_alias=$ac_optarg ;; + + -cache-file | --cache-file | --cache-fil | --cache-fi \ + | --cache-f | --cache- | --cache | --cach | --cac | --ca | --c) + ac_prev=cache_file ;; + -cache-file=* | --cache-file=* | --cache-fil=* | --cache-fi=* \ + | --cache-f=* | --cache-=* | --cache=* | --cach=* | --cac=* | --ca=* | --c=*) + cache_file=$ac_optarg ;; + + --config-cache | -C) + cache_file=config.cache ;; + + -datadir | --datadir | --datadi | --datad) + ac_prev=datadir ;; + -datadir=* | --datadir=* | --datadi=* | --datad=*) + datadir=$ac_optarg ;; + + -datarootdir | --datarootdir | --datarootdi | --datarootd | --dataroot \ + | --dataroo | --dataro | --datar) + ac_prev=datarootdir ;; + -datarootdir=* | --datarootdir=* | --datarootdi=* | --datarootd=* \ + | --dataroot=* | --dataroo=* | --dataro=* | --datar=*) + datarootdir=$ac_optarg ;; + + -disable-* | --disable-*) + ac_useropt=`expr "x$ac_option" : 'x-*disable-\(.*\)'` + # Reject names that are not valid shell variable names. + expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && + as_fn_error "invalid feature name: $ac_useropt" + ac_useropt_orig=$ac_useropt + ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` + case $ac_user_opts in + *" +"enable_$ac_useropt" +"*) ;; + *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--disable-$ac_useropt_orig" + ac_unrecognized_sep=', ';; + esac + eval enable_$ac_useropt=no ;; + + -docdir | --docdir | --docdi | --doc | --do) + ac_prev=docdir ;; + -docdir=* | --docdir=* | --docdi=* | --doc=* | --do=*) + docdir=$ac_optarg ;; + + -dvidir | --dvidir | --dvidi | --dvid | --dvi | --dv) + ac_prev=dvidir ;; + -dvidir=* | --dvidir=* | --dvidi=* | --dvid=* | --dvi=* | --dv=*) + dvidir=$ac_optarg ;; + + -enable-* | --enable-*) + ac_useropt=`expr "x$ac_option" : 'x-*enable-\([^=]*\)'` + # Reject names that are not valid shell variable names. + expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && + as_fn_error "invalid feature name: $ac_useropt" + ac_useropt_orig=$ac_useropt + ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` + case $ac_user_opts in + *" +"enable_$ac_useropt" +"*) ;; + *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--enable-$ac_useropt_orig" + ac_unrecognized_sep=', ';; + esac + eval enable_$ac_useropt=\$ac_optarg ;; + + -exec-prefix | --exec_prefix | --exec-prefix | --exec-prefi \ + | --exec-pref | --exec-pre | --exec-pr | --exec-p | --exec- \ + | --exec | --exe | --ex) + ac_prev=exec_prefix ;; + -exec-prefix=* | --exec_prefix=* | --exec-prefix=* | --exec-prefi=* \ + | --exec-pref=* | --exec-pre=* | --exec-pr=* | --exec-p=* | --exec-=* \ + | --exec=* | --exe=* | --ex=*) + exec_prefix=$ac_optarg ;; + + -gas | --gas | --ga | --g) + # Obsolete; use --with-gas. + with_gas=yes ;; + + -help | --help | --hel | --he | -h) + ac_init_help=long ;; + -help=r* | --help=r* | --hel=r* | --he=r* | -hr*) + ac_init_help=recursive ;; + -help=s* | --help=s* | --hel=s* | --he=s* | -hs*) + ac_init_help=short ;; + + -host | --host | --hos | --ho) + ac_prev=host_alias ;; + -host=* | --host=* | --hos=* | --ho=*) + host_alias=$ac_optarg ;; + + -htmldir | --htmldir | --htmldi | --htmld | --html | --htm | --ht) + ac_prev=htmldir ;; + -htmldir=* | --htmldir=* | --htmldi=* | --htmld=* | --html=* | --htm=* \ + | --ht=*) + htmldir=$ac_optarg ;; + + -includedir | --includedir | --includedi | --included | --include \ + | --includ | --inclu | --incl | --inc) + ac_prev=includedir ;; + -includedir=* | --includedir=* | --includedi=* | --included=* | --include=* \ + | --includ=* | --inclu=* | --incl=* | --inc=*) + includedir=$ac_optarg ;; + + -infodir | --infodir | --infodi | --infod | --info | --inf) + ac_prev=infodir ;; + -infodir=* | --infodir=* | --infodi=* | --infod=* | --info=* | --inf=*) + infodir=$ac_optarg ;; + + -libdir | --libdir | --libdi | --libd) + ac_prev=libdir ;; + -libdir=* | --libdir=* | --libdi=* | --libd=*) + libdir=$ac_optarg ;; + + -libexecdir | --libexecdir | --libexecdi | --libexecd | --libexec \ + | --libexe | --libex | --libe) + ac_prev=libexecdir ;; + -libexecdir=* | --libexecdir=* | --libexecdi=* | --libexecd=* | --libexec=* \ + | --libexe=* | --libex=* | --libe=*) + libexecdir=$ac_optarg ;; + + -localedir | --localedir | --localedi | --localed | --locale) + ac_prev=localedir ;; + -localedir=* | --localedir=* | --localedi=* | --localed=* | --locale=*) + localedir=$ac_optarg ;; + + -localstatedir | --localstatedir | --localstatedi | --localstated \ + | --localstate | --localstat | --localsta | --localst | --locals) + ac_prev=localstatedir ;; + -localstatedir=* | --localstatedir=* | --localstatedi=* | --localstated=* \ + | --localstate=* | --localstat=* | --localsta=* | --localst=* | --locals=*) + localstatedir=$ac_optarg ;; + + -mandir | --mandir | --mandi | --mand | --man | --ma | --m) + ac_prev=mandir ;; + -mandir=* | --mandir=* | --mandi=* | --mand=* | --man=* | --ma=* | --m=*) + mandir=$ac_optarg ;; + + -nfp | --nfp | --nf) + # Obsolete; use --without-fp. + with_fp=no ;; + + -no-create | --no-create | --no-creat | --no-crea | --no-cre \ + | --no-cr | --no-c | -n) + no_create=yes ;; + + -no-recursion | --no-recursion | --no-recursio | --no-recursi \ + | --no-recurs | --no-recur | --no-recu | --no-rec | --no-re | --no-r) + no_recursion=yes ;; + + -oldincludedir | --oldincludedir | --oldincludedi | --oldincluded \ + | --oldinclude | --oldinclud | --oldinclu | --oldincl | --oldinc \ + | --oldin | --oldi | --old | --ol | --o) + ac_prev=oldincludedir ;; + -oldincludedir=* | --oldincludedir=* | --oldincludedi=* | --oldincluded=* \ + | --oldinclude=* | --oldinclud=* | --oldinclu=* | --oldincl=* | --oldinc=* \ + | --oldin=* | --oldi=* | --old=* | --ol=* | --o=*) + oldincludedir=$ac_optarg ;; + + -prefix | --prefix | --prefi | --pref | --pre | --pr | --p) + ac_prev=prefix ;; + -prefix=* | --prefix=* | --prefi=* | --pref=* | --pre=* | --pr=* | --p=*) + prefix=$ac_optarg ;; + + -program-prefix | --program-prefix | --program-prefi | --program-pref \ + | --program-pre | --program-pr | --program-p) + ac_prev=program_prefix ;; + -program-prefix=* | --program-prefix=* | --program-prefi=* \ + | --program-pref=* | --program-pre=* | --program-pr=* | --program-p=*) + program_prefix=$ac_optarg ;; + + -program-suffix | --program-suffix | --program-suffi | --program-suff \ + | --program-suf | --program-su | --program-s) + ac_prev=program_suffix ;; + -program-suffix=* | --program-suffix=* | --program-suffi=* \ + | --program-suff=* | --program-suf=* | --program-su=* | --program-s=*) + program_suffix=$ac_optarg ;; + + -program-transform-name | --program-transform-name \ + | --program-transform-nam | --program-transform-na \ + | --program-transform-n | --program-transform- \ + | --program-transform | --program-transfor \ + | --program-transfo | --program-transf \ + | --program-trans | --program-tran \ + | --progr-tra | --program-tr | --program-t) + ac_prev=program_transform_name ;; + -program-transform-name=* | --program-transform-name=* \ + | --program-transform-nam=* | --program-transform-na=* \ + | --program-transform-n=* | --program-transform-=* \ + | --program-transform=* | --program-transfor=* \ + | --program-transfo=* | --program-transf=* \ + | --program-trans=* | --program-tran=* \ + | --progr-tra=* | --program-tr=* | --program-t=*) + program_transform_name=$ac_optarg ;; + + -pdfdir | --pdfdir | --pdfdi | --pdfd | --pdf | --pd) + ac_prev=pdfdir ;; + -pdfdir=* | --pdfdir=* | --pdfdi=* | --pdfd=* | --pdf=* | --pd=*) + pdfdir=$ac_optarg ;; + + -psdir | --psdir | --psdi | --psd | --ps) + ac_prev=psdir ;; + -psdir=* | --psdir=* | --psdi=* | --psd=* | --ps=*) + psdir=$ac_optarg ;; + + -q | -quiet | --quiet | --quie | --qui | --qu | --q \ + | -silent | --silent | --silen | --sile | --sil) + silent=yes ;; + + -sbindir | --sbindir | --sbindi | --sbind | --sbin | --sbi | --sb) + ac_prev=sbindir ;; + -sbindir=* | --sbindir=* | --sbindi=* | --sbind=* | --sbin=* \ + | --sbi=* | --sb=*) + sbindir=$ac_optarg ;; + + -sharedstatedir | --sharedstatedir | --sharedstatedi \ + | --sharedstated | --sharedstate | --sharedstat | --sharedsta \ + | --sharedst | --shareds | --shared | --share | --shar \ + | --sha | --sh) + ac_prev=sharedstatedir ;; + -sharedstatedir=* | --sharedstatedir=* | --sharedstatedi=* \ + | --sharedstated=* | --sharedstate=* | --sharedstat=* | --sharedsta=* \ + | --sharedst=* | --shareds=* | --shared=* | --share=* | --shar=* \ + | --sha=* | --sh=*) + sharedstatedir=$ac_optarg ;; + + -site | --site | --sit) + ac_prev=site ;; + -site=* | --site=* | --sit=*) + site=$ac_optarg ;; + + -srcdir | --srcdir | --srcdi | --srcd | --src | --sr) + ac_prev=srcdir ;; + -srcdir=* | --srcdir=* | --srcdi=* | --srcd=* | --src=* | --sr=*) + srcdir=$ac_optarg ;; + + -sysconfdir | --sysconfdir | --sysconfdi | --sysconfd | --sysconf \ + | --syscon | --sysco | --sysc | --sys | --sy) + ac_prev=sysconfdir ;; + -sysconfdir=* | --sysconfdir=* | --sysconfdi=* | --sysconfd=* | --sysconf=* \ + | --syscon=* | --sysco=* | --sysc=* | --sys=* | --sy=*) + sysconfdir=$ac_optarg ;; + + -target | --target | --targe | --targ | --tar | --ta | --t) + ac_prev=target_alias ;; + -target=* | --target=* | --targe=* | --targ=* | --tar=* | --ta=* | --t=*) + target_alias=$ac_optarg ;; + + -v | -verbose | --verbose | --verbos | --verbo | --verb) + verbose=yes ;; + + -version | --version | --versio | --versi | --vers | -V) + ac_init_version=: ;; + + -with-* | --with-*) + ac_useropt=`expr "x$ac_option" : 'x-*with-\([^=]*\)'` + # Reject names that are not valid shell variable names. + expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && + as_fn_error "invalid package name: $ac_useropt" + ac_useropt_orig=$ac_useropt + ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` + case $ac_user_opts in + *" +"with_$ac_useropt" +"*) ;; + *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--with-$ac_useropt_orig" + ac_unrecognized_sep=', ';; + esac + eval with_$ac_useropt=\$ac_optarg ;; + + -without-* | --without-*) + ac_useropt=`expr "x$ac_option" : 'x-*without-\(.*\)'` + # Reject names that are not valid shell variable names. + expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && + as_fn_error "invalid package name: $ac_useropt" + ac_useropt_orig=$ac_useropt + ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` + case $ac_user_opts in + *" +"with_$ac_useropt" +"*) ;; + *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--without-$ac_useropt_orig" + ac_unrecognized_sep=', ';; + esac + eval with_$ac_useropt=no ;; + + --x) + # Obsolete; use --with-x. + with_x=yes ;; + + -x-includes | --x-includes | --x-include | --x-includ | --x-inclu \ + | --x-incl | --x-inc | --x-in | --x-i) + ac_prev=x_includes ;; + -x-includes=* | --x-includes=* | --x-include=* | --x-includ=* | --x-inclu=* \ + | --x-incl=* | --x-inc=* | --x-in=* | --x-i=*) + x_includes=$ac_optarg ;; + + -x-libraries | --x-libraries | --x-librarie | --x-librari \ + | --x-librar | --x-libra | --x-libr | --x-lib | --x-li | --x-l) + ac_prev=x_libraries ;; + -x-libraries=* | --x-libraries=* | --x-librarie=* | --x-librari=* \ + | --x-librar=* | --x-libra=* | --x-libr=* | --x-lib=* | --x-li=* | --x-l=*) + x_libraries=$ac_optarg ;; + + -*) as_fn_error "unrecognized option: \`$ac_option' +Try \`$0 --help' for more information." + ;; + + *=*) + ac_envvar=`expr "x$ac_option" : 'x\([^=]*\)='` + # Reject names that are not valid shell variable names. + case $ac_envvar in #( + '' | [0-9]* | *[!_$as_cr_alnum]* ) + as_fn_error "invalid variable name: \`$ac_envvar'" ;; + esac + eval $ac_envvar=\$ac_optarg + export $ac_envvar ;; + + *) + # FIXME: should be removed in autoconf 3.0. + $as_echo "$as_me: WARNING: you should use --build, --host, --target" >&2 + expr "x$ac_option" : ".*[^-._$as_cr_alnum]" >/dev/null && + $as_echo "$as_me: WARNING: invalid host type: $ac_option" >&2 + : ${build_alias=$ac_option} ${host_alias=$ac_option} ${target_alias=$ac_option} + ;; + + esac +done + +if test -n "$ac_prev"; then + ac_option=--`echo $ac_prev | sed 's/_/-/g'` + as_fn_error "missing argument to $ac_option" +fi + +if test -n "$ac_unrecognized_opts"; then + case $enable_option_checking in + no) ;; + fatal) as_fn_error "unrecognized options: $ac_unrecognized_opts" ;; + *) $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2 ;; + esac +fi + +# Check all directory arguments for consistency. +for ac_var in exec_prefix prefix bindir sbindir libexecdir datarootdir \ + datadir sysconfdir sharedstatedir localstatedir includedir \ + oldincludedir docdir infodir htmldir dvidir pdfdir psdir \ + libdir localedir mandir +do + eval ac_val=\$$ac_var + # Remove trailing slashes. + case $ac_val in + */ ) + ac_val=`expr "X$ac_val" : 'X\(.*[^/]\)' \| "X$ac_val" : 'X\(.*\)'` + eval $ac_var=\$ac_val;; + esac + # Be sure to have absolute directory names. + case $ac_val in + [\\/$]* | ?:[\\/]* ) continue;; + NONE | '' ) case $ac_var in *prefix ) continue;; esac;; + esac + as_fn_error "expected an absolute directory name for --$ac_var: $ac_val" +done + +# There might be people who depend on the old broken behavior: `$host' +# used to hold the argument of --host etc. +# FIXME: To remove some day. +build=$build_alias +host=$host_alias +target=$target_alias + +# FIXME: To remove some day. +if test "x$host_alias" != x; then + if test "x$build_alias" = x; then + cross_compiling=maybe + $as_echo "$as_me: WARNING: If you wanted to set the --build type, don't use --host. + If a cross compiler is detected then cross compile mode will be used." >&2 + elif test "x$build_alias" != "x$host_alias"; then + cross_compiling=yes + fi +fi + +ac_tool_prefix= +test -n "$host_alias" && ac_tool_prefix=$host_alias- + +test "$silent" = yes && exec 6>/dev/null + + +ac_pwd=`pwd` && test -n "$ac_pwd" && +ac_ls_di=`ls -di .` && +ac_pwd_ls_di=`cd "$ac_pwd" && ls -di .` || + as_fn_error "working directory cannot be determined" +test "X$ac_ls_di" = "X$ac_pwd_ls_di" || + as_fn_error "pwd does not report name of working directory" + + +# Find the source files, if location was not specified. +if test -z "$srcdir"; then + ac_srcdir_defaulted=yes + # Try the directory containing this script, then the parent directory. + ac_confdir=`$as_dirname -- "$as_myself" || +$as_expr X"$as_myself" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ + X"$as_myself" : 'X\(//\)[^/]' \| \ + X"$as_myself" : 'X\(//\)$' \| \ + X"$as_myself" : 'X\(/\)' \| . 2>/dev/null || +$as_echo X"$as_myself" | + sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ + s//\1/ + q + } + /^X\(\/\/\)[^/].*/{ + s//\1/ + q + } + /^X\(\/\/\)$/{ + s//\1/ + q + } + /^X\(\/\).*/{ + s//\1/ + q + } + s/.*/./; q'` + srcdir=$ac_confdir + if test ! -r "$srcdir/$ac_unique_file"; then + srcdir=.. + fi +else + ac_srcdir_defaulted=no +fi +if test ! -r "$srcdir/$ac_unique_file"; then + test "$ac_srcdir_defaulted" = yes && srcdir="$ac_confdir or .." + as_fn_error "cannot find sources ($ac_unique_file) in $srcdir" +fi +ac_msg="sources are in $srcdir, but \`cd $srcdir' does not work" +ac_abs_confdir=`( + cd "$srcdir" && test -r "./$ac_unique_file" || as_fn_error "$ac_msg" + pwd)` +# When building in place, set srcdir=. +if test "$ac_abs_confdir" = "$ac_pwd"; then + srcdir=. +fi +# Remove unnecessary trailing slashes from srcdir. +# Double slashes in file names in object file debugging info +# mess up M-x gdb in Emacs. +case $srcdir in +*/) srcdir=`expr "X$srcdir" : 'X\(.*[^/]\)' \| "X$srcdir" : 'X\(.*\)'`;; +esac +for ac_var in $ac_precious_vars; do + eval ac_env_${ac_var}_set=\${${ac_var}+set} + eval ac_env_${ac_var}_value=\$${ac_var} + eval ac_cv_env_${ac_var}_set=\${${ac_var}+set} + eval ac_cv_env_${ac_var}_value=\$${ac_var} +done + +# +# Report the --help message. +# +if test "$ac_init_help" = "long"; then + # Omit some internal or obsolete options to make the list less imposing. + # This message is too long to be a string in the A/UX 3.1 sh. + cat <<_ACEOF +\`configure' configures BRugs 0.7 to adapt to many kinds of systems. + +Usage: $0 [OPTION]... [VAR=VALUE]... + +To assign environment variables (e.g., CC, CFLAGS...), specify them as +VAR=VALUE. See below for descriptions of some of the useful variables. + +Defaults for the options are specified in brackets. + +Configuration: + -h, --help display this help and exit + --help=short display options specific to this package + --help=recursive display the short help of all the included packages + -V, --version display version information and exit + -q, --quiet, --silent do not print \`checking...' messages + --cache-file=FILE cache test results in FILE [disabled] + -C, --config-cache alias for \`--cache-file=config.cache' + -n, --no-create do not create output files + --srcdir=DIR find the sources in DIR [configure dir or \`..'] + +Installation directories: + --prefix=PREFIX install architecture-independent files in PREFIX + [$ac_default_prefix] + --exec-prefix=EPREFIX install architecture-dependent files in EPREFIX + [PREFIX] + +By default, \`make install' will install all the files in +\`$ac_default_prefix/bin', \`$ac_default_prefix/lib' etc. You can specify +an installation prefix ... [truncated message content] |
From: <chr...@us...> - 2011-03-23 11:58:22
|
Revision: 183 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=183&view=rev Author: chris-jackson Date: 2011-03-23 11:58:16 +0000 (Wed, 23 Mar 2011) Log Message: ----------- Bug fixes ready for version 0.7 release on OpenBUGS wiki Modified Paths: -------------- branches/linux/BRugs/R/unix/zzz.R branches/linux/BRugs/R/unix/zzz.R.in branches/linux/BRugs/R/windows/zzz.R branches/linux/BRugs/R/zzz.R branches/linux/BRugs/src/Makevars Modified: branches/linux/BRugs/R/unix/zzz.R =================================================================== --- branches/linux/BRugs/R/unix/zzz.R 2011-03-22 12:24:38 UTC (rev 182) +++ branches/linux/BRugs/R/unix/zzz.R 2011-03-23 11:58:16 UTC (rev 183) @@ -4,12 +4,15 @@ ## TODO any need for these to be user specifiable? options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) - options(OpenBUGS = "/home/chris/usr/lib/OpenBUGS") + options(OpenBUGS = "/usr/local/lib/OpenBUGS") if(is.null(getOption("BRugsVerbose"))) options("BRugsVerbose" = TRUE) .initGlobals() options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) + ver <- system("echo \"modelQuit()\" | OpenBUGS", intern=TRUE) + ver <- sub("OpenBUGS version (([0-9]\\.)+[0-9]).+","\\1",ver[1]) + message("Welcome to BRugs running on OpenBUGS version ", ver) } ".onUnload" <- function(libpath){ Modified: branches/linux/BRugs/R/unix/zzz.R.in =================================================================== --- branches/linux/BRugs/R/unix/zzz.R.in 2011-03-22 12:24:38 UTC (rev 182) +++ branches/linux/BRugs/R/unix/zzz.R.in 2011-03-23 11:58:16 UTC (rev 183) @@ -10,6 +10,9 @@ options("BRugsVerbose" = TRUE) .initGlobals() options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) + ver <- system("echo \"modelQuit()\" | OpenBUGS", intern=TRUE) + ver <- sub("OpenBUGS version (([0-9]\\.)+[0-9]).+","\\1",ver[1]) + message("Welcome to BRugs running on OpenBUGS version ", ver) } ".onUnload" <- function(libpath){ Modified: branches/linux/BRugs/R/windows/zzz.R =================================================================== --- branches/linux/BRugs/R/windows/zzz.R 2011-03-22 12:24:38 UTC (rev 182) +++ branches/linux/BRugs/R/windows/zzz.R 2011-03-23 11:58:16 UTC (rev 183) @@ -2,36 +2,47 @@ ".onLoad" <- function(lib, pkg){ ob.reg <- try(utils:::readRegistry("Software\\OpenBUGS","HLM")) - if (inherits(ob.reg, "try-error")) stop("OpenBUGS 3.2.1 or greater must be installed") + if (inherits(ob.reg, "try-error")) { + warning("OpenBUGS 3.2.1 or greater must be installed") + return + } rnames <- names(ob.reg) ver <- gsub("OpenBUGS ", "", rnames) - ver <- gsub("(.+)e$","\\1", ver) - version.inst <- as.numeric(paste(substr(ver, 1, 2), gsub("\\.","",substr(ver, 3, nchar(ver))), sep="")) + veri <- gsub("(.+)e$","\\1", ver) + version.inst <- as.numeric(paste(substr(veri, 1, 2), gsub("\\.","",substr(veri, 3, nchar(veri))), sep="")) deps <- utils:::packageDescription("BRugs", fields="SystemRequirements") ver <- gsub(".*OpenBUGS ?\\(>= ?(.+)\\).*", "\\1", deps) version.req <- as.numeric(paste(substr(ver, 1, 2), gsub("\\.","",substr(ver, 3, nchar(ver))), sep="")) - if (max(version.inst) < version.req) - stop("Found OpenBUGS version ", version.inst, ". Requires ", version.req, " or greater") + if (max(version.inst) < version.req) { + warning("Found OpenBUGS version ", version.inst, ". Requires ", version.req, " or greater") + return + } ## OpenBUGS installation location - options(OpenBUGS = utils:::readRegistry(paste("Software","OpenBUGS",rnames[which.max(version.inst)],sep="\\"),"HLM")$InstallPath) - libname <- paste(options()$OpenBUGS, "libOpenBUGS.dll", sep="/") + dir <- utils:::readRegistry(paste("Software","OpenBUGS",rnames[which.max(version.inst)],sep="\\"),"HLM")$InstallPath + loadOpenBUGS(dir) + message("Welcome to BRugs running on OpenBUGS version ", veri[which.max(version.inst)]) + } + + ## Load OpenBUGS from specified location + loadOpenBUGS <- function(dir) { + libname <- paste(dir, "libOpenBUGS.dll", sep="/") if (!file.exists(libname)) { - stop("Shared library \"libOpenBUGS.dll\" not found in ", options()$OpenBUGS) + warning("Shared library \"libOpenBUGS.dll\" not found in ", dir) } + options(OpenBUGS = dir) ## All checks passed - load the DLL dyn.load(libname) - len <- nchar(options()$OpenBUGS) - .C("SetWorkingDir", as.character(options()$OpenBUGS), len, PACKAGE="libOpenBUGS") + len <- nchar(dir) + .C("SetWorkingDir", as.character(dir), len, PACKAGE="libOpenBUGS") ## Set temporary dir for "buffer.txt" output tempDir <- gsub("\\\\", "/", tempdir()) .C("SetTempDir", as.character(tempDir), nchar(tempDir), PACKAGE="libOpenBUGS") command <- "BugsMappers.SetDest(2)" .CmdInterpreter(command) - if(is.null(getOption("BRugsVerbose"))) options("BRugsVerbose" = TRUE) .initGlobals() - options(OpenBUGSExamples = paste(options()$OpenBUGS, "Examples", sep="/")) + options(OpenBUGSExamples = paste(dir, "Examples", sep="/")) } ".onUnload" <- function(libpath){ Modified: branches/linux/BRugs/R/zzz.R =================================================================== --- branches/linux/BRugs/R/zzz.R 2011-03-22 12:24:38 UTC (rev 182) +++ branches/linux/BRugs/R/zzz.R 2011-03-23 11:58:16 UTC (rev 183) @@ -1,4 +1,4 @@ -## See unix/zzz.R, windows/zzz.R for platform specific .onLoad functions +## See unix/zzz.R, windows/zzz.R for platform specific .onLoad functions if (is.R()){ @@ -13,10 +13,6 @@ options("BRugsPrec" = 4) } - ".onAttach" <- function(lib, pkg){ - message("Welcome to BRugs running on OpenBUGS version 3.1.2") - } - ## Overwriting new (from R-2.6.0) sQuote (for typing human readable text) in R within the BRugs Namespace! ## we cannot use sQuote that uses fancy quotes! sQuote <- function(x) paste("'", x, "'", sep="") Modified: branches/linux/BRugs/src/Makevars =================================================================== --- branches/linux/BRugs/src/Makevars 2011-03-22 12:24:38 UTC (rev 182) +++ branches/linux/BRugs/src/Makevars 2011-03-23 11:58:16 UTC (rev 183) @@ -1,5 +1,5 @@ -BUGS_LIBS = /home/chris/usr/lib/OpenBUGS/lib/libOpenBUGS.so -BUGS_LDFLAGS = -m32 -Wl,-rpath=/home/chris/usr/lib/OpenBUGS/lib +BUGS_LIBS = /usr/local/lib/OpenBUGS/lib/libOpenBUGS.so +BUGS_LDFLAGS = -m32 -Wl,-rpath=/usr/local/lib/OpenBUGS/lib BugsHelper: mkdir -p ../exec This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <chr...@us...> - 2011-04-21 16:51:43
|
Revision: 187 http://bugs-r.svn.sourceforge.net/bugs-r/?rev=187&view=rev Author: chris-jackson Date: 2011-04-21 16:51:36 +0000 (Thu, 21 Apr 2011) Log Message: ----------- Changes for version 0.7 1 (see NEWS) Modified Paths: -------------- branches/linux/BRugs/DESCRIPTION branches/linux/BRugs/NAMESPACE branches/linux/BRugs/NEWS branches/linux/BRugs/R/bugs.data.R branches/linux/BRugs/R/internal.R branches/linux/BRugs/R/unix/help.R branches/linux/BRugs/R/unix/zzz.R branches/linux/BRugs/R/unix/zzz.R.in branches/linux/BRugs/R/windows/zzz.R branches/linux/BRugs/configure branches/linux/BRugs/configure.ac branches/linux/BRugs/src/Makevars branches/linux/BRugs/tests/BRugs.R branches/linux/BRugs/tests/examples.R branches/linux/BRugs/tests/functions.R Added Paths: ----------- branches/linux/BRugs/man/windows/ branches/linux/BRugs/man/windows/loadOpenBUGS.Rd Modified: branches/linux/BRugs/DESCRIPTION =================================================================== --- branches/linux/BRugs/DESCRIPTION 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/DESCRIPTION 2011-04-21 16:51:36 UTC (rev 187) @@ -1,8 +1,8 @@ Package: BRugs Title: R interface to the OpenBUGS MCMC software -Version: 0.7 -Date: 2011-03-07 -Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R interface developed by Uwe Ligges, Sibylle Sturtz, Andrew Gelman, Gregor Gorjanc and Chris Jackson. Linux port and most recent developments by Chris Jackson. +Version: 0.7.1 +Date: 2011-04-19 +Author: OpenBUGS was developed by Andrew Thomas, Dave Lunn, David Spiegelhalter and Nicky Best. R interface developed by Uwe Ligges, Sibylle Sturtz, Andrew Gelman, Gregor Gorjanc and Chris Jackson. Linux port and most recent developments by Chris Jackson. Description: Fully-interactive R interface to the OpenBUGS software for Bayesian analysis using MCMC sampling Maintainer: Chris Jackson <chr...@mr...> Depends: R (>= 2.5.0), utils, coda Modified: branches/linux/BRugs/NAMESPACE =================================================================== --- branches/linux/BRugs/NAMESPACE 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/NAMESPACE 2011-04-21 16:51:36 UTC (rev 187) @@ -4,6 +4,7 @@ getNumChains, help.BRugs, help.WinBUGS, infoMemory,infoModules,infoNodeValues,infoNodeMethods,infoNodeTypes, infoUpdatersbyName,infoUpdatersbyDepth, +loadOpenBUGS, modelAdaptivePhase, modelCheck, modelCompile, modelData, modelGenInits, modelInits, modelIteration, modelNames, modelPrecision, modelSaveState, Modified: branches/linux/BRugs/NEWS =================================================================== --- branches/linux/BRugs/NEWS 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/NEWS 2011-04-21 16:51:36 UTC (rev 187) @@ -1,8 +1,27 @@ -Version 0.7 +Version 0.7.1 (19 April 2011) +------------- + +The configure script on Linux now automatically detects OpenBUGS +installed by the RPM and DEB packages (to standards-compliant +locations) as well as OpenBUGS installed by the source package. + +Bug fix - bugsData should accept data as a list of variable names. +Thanks to Brian Ripley for these reports. + +handleRes() now explicitly labels internal OpenBUGS traps as bugs and +asks the user to send a bug report to the package maintainer. + +On Windows, if OpenBUGS installation is not detected in the registry, +package loading continues with a warning instead of stopping with an +error. If OpenBUGS was actually installed, the user can then load it +from a specified directory with loadOpenBUGS(dir). + + +Version 0.7 (March 2011) ----------- BRugs now works with an existing installation of OpenBUGS (3.2.1 or -later) instead of being distributed with the OpenBUGS library. +later) instead of being distributed with the OpenBUGS library. On Windows, the OpenBUGS location is determined by a registry key which is installed by the OpenBUGS for Windows installation program. @@ -12,25 +31,25 @@ for Linux source package OpenBUGS-3.2.1.tar.gz or later, this library directory is by default -/usr/local/lib/OpenBUGS +/usr/local/lib/OpenBUGS In most cases it should be detected automatically when installing, but it can be changed by running, for instance -R CMD INSTALL --configure-args='--with-openbugs=/usr/lib/OpenBUGS' +R CMD INSTALL --configure-args='--with-openbugs=/usr/lib/OpenBUGS' Version 0.61 ------------ -Fix for crash in bugsData +Fix for crash in bugsData -Version 0.6 +Version 0.6 ----------- Forked from the version of BRugs (0.5.3) available on CRAN Extras. -This new version supports Linux for the first time, as detailed below. +This new version supports Linux for the first time, as detailed below. CHANGES MADE FOR LINUX PORT OF BRugs @@ -40,7 +59,7 @@ any number of different OpenBUGS API commands can be run. The state of the model is "internalized" on entry from a file in the temporary directory, and "externalized" on exit. The source is in src/ and - the binary is installed into exec/. + the binary is installed into exec/. * New function .OpenBUGS() to execute a sequence of OpenBUGS API commands of possibly differing types (e.g. CmdInterpreter, Modified: branches/linux/BRugs/R/bugs.data.R =================================================================== --- branches/linux/BRugs/R/bugs.data.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/bugs.data.R 2011-04-21 16:51:36 UTC (rev 187) @@ -1,28 +1,29 @@ "bugsData" <- -function(data, fileName = file.path(tempdir(), "data.txt"), format="E", digits = 5){ - if(is.list(data)) { - data <- lapply(data, function(x){x <- if(is.character(x)||is.factor(x)) match(x, unique(x)) else x}) - if(is.R()) { - write.datafile(lapply(data, formatC, digits = digits, format = format), fileName) + function(data, fileName = file.path(tempdir(), "data.txt"), format="E", digits = 5){ + if (is.character(unlist(data))) { + if(is.R()) { + data.list <- lapply(as.list(data), get, pos = parent.frame(2)) + names(data.list) <- as.list(data) + write.datafile(lapply(data.list, formatC, digits = digits, format = format), fileName) + } + else { + data.list <- lapply(as.list(data), get, where = parent.frame(2)) + names(data.list) <- unlist(data) + writeDatafileS4(data.list, towhere = "data.txt") + } } - else { - writeDatafileS4(data, towhere = "data.txt") + else if(is.list(data)) { + data <- lapply(data, function(x){x <- if(is.character(x)||is.factor(x)) match(x, unique(x)) else x}) + if(is.R()) { + write.datafile(lapply(data, formatC, digits = digits, format = format), fileName) + } + else { + writeDatafileS4(data, towhere = "data.txt") + } } - } - else { - if(is.R()) { - data.list <- lapply(as.list(data), get, pos = parent.frame(2)) - names(data.list) <- as.list(data) - write.datafile(lapply(data.list, formatC, digits = digits, format = format), fileName) - } - else { - data.list <- lapply(as.list(data), get, where = parent.frame(2)) - names(data.list) <- unlist(data) - writeDatafileS4(data.list, towhere = "data.txt") - } + else stop("Expected a list of data, a list or vector of variable names") + invisible(fileName) } - invisible(fileName) -} if(is.R()){ Modified: branches/linux/BRugs/R/internal.R =================================================================== --- branches/linux/BRugs/R/internal.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/internal.R 2011-04-21 16:51:36 UTC (rev 187) @@ -34,10 +34,12 @@ handleRes <- function(res) { - switch(res, - stop("An OpenBUGS module or procedure was called that did not exist."), - stop("An OpenBUGS procedure was called with the wrong type of argument."), - stop("An OpenBUGS procedure was called with the wrong signature.")) + maintainer <- utils:::packageDescription("BRugs", fields="Maintainer") + switch(res, + stop("An OpenBUGS module or procedure was called that did not exist. Please report this bug to ", maintainer), + stop("An OpenBUGS procedure was called with the wrong type of argument. Please report this bug to ", maintainer), + stop("An OpenBUGS procedure was called with the wrong signature. Please report this bug to ", maintainer) + ) } .SamplesGlobalsCmd <- function(node){ Modified: branches/linux/BRugs/R/unix/help.R =================================================================== --- branches/linux/BRugs/R/unix/help.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/unix/help.R 2011-04-21 16:51:36 UTC (rev 187) @@ -24,6 +24,6 @@ "switch to its window."), exdent = 4)) writeLines("Otherwise, be patient ...") - browseURL(paste(options()$OpenBUGS, "doc", "Manuals", "Contents.html", sep="/")) + browseURL(paste(options()$OpenBUGSdoc, "Manuals", "Contents.html", sep="/")) invisible("") } Modified: branches/linux/BRugs/R/unix/zzz.R =================================================================== --- branches/linux/BRugs/R/unix/zzz.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/unix/zzz.R 2011-04-21 16:51:36 UTC (rev 187) @@ -5,12 +5,13 @@ options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) options(OpenBUGS = "/usr/local/lib/OpenBUGS") + options(OpenBUGSdoc = "/usr/local/lib/OpenBUGS/doc") + options(OpenBUGSExamples = paste(options()$OpenBUGSdoc, "Examples", sep="/")) if(is.null(getOption("BRugsVerbose"))) options("BRugsVerbose" = TRUE) .initGlobals() - options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) - ver <- system("echo \"modelQuit()\" | OpenBUGS", intern=TRUE) + ver <- system("echo \"modelQuit()\" | /usr/local/lib/OpenBUGS/bin/OpenBUGS", intern=TRUE) ver <- sub("OpenBUGS version (([0-9]\\.)+[0-9]).+","\\1",ver[1]) message("Welcome to BRugs running on OpenBUGS version ", ver) } @@ -18,4 +19,7 @@ ".onUnload" <- function(libpath){ } + ## Windows-only + loadOpenBUGS <- function(dir) { + } } Modified: branches/linux/BRugs/R/unix/zzz.R.in =================================================================== --- branches/linux/BRugs/R/unix/zzz.R.in 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/unix/zzz.R.in 2011-04-21 16:51:36 UTC (rev 187) @@ -5,12 +5,13 @@ options("BRugsTmpdir" = gsub("\\\\", "/", tempdir())) options("BRugsExtFile" = paste(basename(tempfile()), ".bug", sep="")) options(OpenBUGS = "@OPENBUGS@") + options(OpenBUGSdoc = "@OPENBUGSDOC@") + options(OpenBUGSExamples = paste(options()$OpenBUGSdoc, "Examples", sep="/")) if(is.null(getOption("BRugsVerbose"))) options("BRugsVerbose" = TRUE) .initGlobals() - options(OpenBUGSExamples = paste(options()$OpenBUGS, "doc", "Examples", sep="/")) - ver <- system("echo \"modelQuit()\" | OpenBUGS", intern=TRUE) + ver <- system("echo \"modelQuit()\" | @OPENBUGS@/bin/OpenBUGS", intern=TRUE) ver <- sub("OpenBUGS version (([0-9]\\.)+[0-9]).+","\\1",ver[1]) message("Welcome to BRugs running on OpenBUGS version ", ver) } @@ -18,4 +19,7 @@ ".onUnload" <- function(libpath){ } + ## Windows-only + loadOpenBUGS <- function(dir) { + } } Modified: branches/linux/BRugs/R/windows/zzz.R =================================================================== --- branches/linux/BRugs/R/windows/zzz.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/R/windows/zzz.R 2011-04-21 16:51:36 UTC (rev 187) @@ -4,7 +4,7 @@ ob.reg <- try(utils:::readRegistry("Software\\OpenBUGS","HLM")) if (inherits(ob.reg, "try-error")) { warning("OpenBUGS 3.2.1 or greater must be installed") - return + return() } rnames <- names(ob.reg) ver <- gsub("OpenBUGS ", "", rnames) @@ -15,7 +15,7 @@ version.req <- as.numeric(paste(substr(ver, 1, 2), gsub("\\.","",substr(ver, 3, nchar(ver))), sep="")) if (max(version.inst) < version.req) { warning("Found OpenBUGS version ", version.inst, ". Requires ", version.req, " or greater") - return + return() } ## OpenBUGS installation location dir <- utils:::readRegistry(paste("Software","OpenBUGS",rnames[which.max(version.inst)],sep="\\"),"HLM")$InstallPath @@ -28,9 +28,9 @@ libname <- paste(dir, "libOpenBUGS.dll", sep="/") if (!file.exists(libname)) { warning("Shared library \"libOpenBUGS.dll\" not found in ", dir) + return(FALSE) } options(OpenBUGS = dir) - ## All checks passed - load the DLL dyn.load(libname) len <- nchar(dir) .C("SetWorkingDir", as.character(dir), len, PACKAGE="libOpenBUGS") @@ -43,6 +43,7 @@ options("BRugsVerbose" = TRUE) .initGlobals() options(OpenBUGSExamples = paste(dir, "Examples", sep="/")) + invisible() } ".onUnload" <- function(libpath){ Modified: branches/linux/BRugs/configure =================================================================== --- branches/linux/BRugs/configure 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/configure 2011-04-21 16:51:36 UTC (rev 187) @@ -556,6 +556,7 @@ ac_default_prefix=/usr/local ac_subst_vars='LTLIBOBJS LIBOBJS +OPENBUGSDOC OPENBUGS OBJEXT EXEEXT @@ -1225,9 +1226,8 @@ Optional Packages: --with-PACKAGE[=ARG] use PACKAGE [ARG=yes] --without-PACKAGE do not use PACKAGE (same as --with-PACKAGE=no) - --with-openbugs=LIB_PATH - the location of the OpenBUGS installation, by - default /usr/local/lib/OpenBUGS + --with-openbugs=PATH the location of OpenBUGS installed from the source + package, by default /usr/local/lib/OpenBUGS Some influential environment variables: CC C compiler command @@ -1753,9 +1753,19 @@ -## TODO only runs on x86 Linux - give error on other unixes +## Work around the inconsistency between the installation destinations of the 3.2.1 source and binary packages. +## Source installs library in $prefix/lib/OpenBUGS/lib, doc in $prefix/lib/OpenBUGS/doc. +## Binaries install in standards-compliant locations $prefix/lib and $prefix/share/doc/openbugs-version respectively. +## Look in all of these places. +## Return OPENBUGS = $prefix/lib/OpenBUGS for source installations, and +## OPENBUGS = $prefix for binary installations. +## Return OPENBUGSDOC = $prefix/lib/OpenBUGS/doc for source installations, +## and OPENBUGSDOC = $prefix/share/doc/openbugs-version for binary installations. +## If user specifies -with-openbugs, this is interpreted for a source installation. +## TODO only runs on x86 Linux - give error on other unixes. + if test "x$prefix" = xNONE; then $as_echo_n "checking for prefix by " >&6 # Extract the first word of "OpenBUGS", so it can be a program name with args. @@ -1858,18 +1868,23 @@ if test -n "$openbugs_path" ; then OPENBUGS=${openbugs_path} + SOURCEINST=true else - echo ${prefix} - if test "${prefix}" = "NONE" ; then - as_fn_error "\"OpenBUGS installation not found in the default /usr/local/lib/OpenBUGS. Run R CMD INSTALL BRugs --configure-args=' --with-openbugs=...'\"" "$LINENO" 5 + if test "$prefix" = "NONE" ; then + as_fn_error "OpenBUGS not found. Install OpenBUGS 3.2.1 or later, or specify its location using, for example, R CMD INSTALL BRugs --configure-args='--with-openbugs=/usr/local/lib/OpenBUGS' " "$LINENO" 5 else - OPENBUGS=${prefix}/lib/OpenBUGS + if test -e ${prefix}/lib/OpenBUGS/lib/libOpenBUGS.so ; then + OPENBUGS=${prefix}/lib/OpenBUGS + SOURCEINST=true + else + OPENBUGS=${prefix} + SOURCEINST=false + fi fi fi OLDFLAGS=${LDFLAGS} LDFLAGS="-L${OPENBUGS}/lib -m32" -echo $LDFLAGS ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' @@ -2706,19 +2721,31 @@ LIBS="-lOpenBUGS $LIBS" else - as_fn_error "\"Cannot load OpenBUGS library in lib subdirectory of ${OPENBUGS}. Run R CMD INSTALL BRugs --configure-args='--with-openbugs=...'\"" "$LINENO" 5 + as_fn_error "\"Cannot load OpenBUGS library in ${OPENBUGS}/lib. Run R CMD INSTALL BRugs --configure-args='--with-openbugs=...'\"" "$LINENO" 5 fi LDFLAGS=${OLDFLAGS} -## TODO any need to check for version? -## could do with -#VERSION=`echo "modelQuit()" | OpenBUGS | sed -ne "s/OpenBUGS version \(.*\) rev \(.*\)/\1/p` -#if test `echo $VERSION |cut -d. -f1` -lt 3 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi -#if test `echo $VERSION |cut -d. -f2` -lt 2 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi -#if test `echo $VERSION |cut -d. -f3` -lt 1 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi +if ${SOURCEINST} ; then + { $as_echo "$as_me:${as_lineno-$LINENO}: Found OpenBUGS installation from source package " >&5 +$as_echo "$as_me: Found OpenBUGS installation from source package " >&6;} + OPENBUGSDOC=${OPENBUGS}/doc +else + { $as_echo "$as_me:${as_lineno-$LINENO}: Found OpenBUGS installation from binary package " >&5 +$as_echo "$as_me: Found OpenBUGS installation from binary package " >&6;} + OPENBUGSDOC=${OPENBUGS}/share/doc/openbugs-${VERSION} +fi +VERSION=`echo "modelQuit()" | ${OPENBUGS}/bin/OpenBUGS | sed -ne "s/OpenBUGS version \(.*\) rev \(.*\)/\1/p"` +if test `echo ${VERSION} |cut -d. -f1` -lt 3; then + as_fn_error "Requires OpenBUGS version 3.2.1 or greater" "$LINENO" 5 +fi +if test `echo ${VERSION} |cut -d. -f1` -eq 3 -a `echo ${VERSION} |cut -d. -f2` -lt 2 ; then + as_fn_error "Requires OpenBUGS version 3.2.1 or greater" "$LINENO" 5 +fi + + ac_config_files="$ac_config_files src/Makevars" cat >confcache <<\_ACEOF Modified: branches/linux/BRugs/configure.ac =================================================================== --- branches/linux/BRugs/configure.ac 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/configure.ac 2011-04-21 16:51:36 UTC (rev 187) @@ -1,40 +1,65 @@ AC_INIT([BRugs], [0.7]) -## TODO only runs on x86 Linux - give error on other unixes +## Work around the inconsistency between the installation destinations of the 3.2.1 source and binary packages. +## Source installs library in $prefix/lib/OpenBUGS/lib, doc in $prefix/lib/OpenBUGS/doc. +## Binaries install in standards-compliant locations $prefix/lib and $prefix/share/doc/openbugs-version respectively. +## Look in all of these places. +## Return OPENBUGS = $prefix/lib/OpenBUGS for source installations, and +## OPENBUGS = $prefix for binary installations. +## Return OPENBUGSDOC = $prefix/lib/OpenBUGS/doc for source installations, +## and OPENBUGSDOC = $prefix/share/doc/openbugs-version for binary installations. +## If user specifies -with-openbugs, this is interpreted for a source installation. +## TODO only runs on x86 Linux - give error on other unixes. + AC_PREFIX_DEFAULT(/usr/local) AC_PREFIX_PROGRAM([OpenBUGS]) AC_ARG_WITH([openbugs], - AC_HELP_STRING([--with-openbugs=LIB_PATH], - [the location of the OpenBUGS installation, by default /usr/local/lib/OpenBUGS]), + AC_HELP_STRING([--with-openbugs=PATH], + [the location of OpenBUGS installed from the source package, by default /usr/local/lib/OpenBUGS]), [openbugs_path=$withval]) if test [ -n "$openbugs_path" ] ; then OPENBUGS=${openbugs_path} + SOURCEINST=true else - echo ${prefix} - if test [ "${prefix}" = "NONE" ] ; then - AC_MSG_ERROR("OpenBUGS installation not found in the default /usr/local/lib/OpenBUGS. Run R CMD INSTALL BRugs --configure-args=' --with-openbugs=...'") + if test [ "$prefix" = "NONE" ]; then + AC_MSG_ERROR( [OpenBUGS not found. Install OpenBUGS 3.2.1 or later, or specify its location using, for example, R CMD INSTALL BRugs --configure-args='--with-openbugs=/usr/local/lib/OpenBUGS'] ) else - OPENBUGS=${prefix}/lib/OpenBUGS + if test [ -e ${prefix}/lib/OpenBUGS/lib/libOpenBUGS.so ] ; then + OPENBUGS=${prefix}/lib/OpenBUGS + SOURCEINST=true + else + OPENBUGS=${prefix} + SOURCEINST=false + fi fi fi OLDFLAGS=${LDFLAGS} LDFLAGS="-L${OPENBUGS}/lib -m32" -echo $LDFLAGS AC_CHECK_LIB(OpenBUGS, CmdInterpreter, [], - [AC_MSG_ERROR("Cannot load OpenBUGS library in lib subdirectory of ${OPENBUGS}. Run R CMD INSTALL BRugs --configure-args='--with-openbugs=...'")]) + [AC_MSG_ERROR("Cannot load OpenBUGS library in ${OPENBUGS}/lib. Run R CMD INSTALL BRugs --configure-args='--with-openbugs=...'")]) LDFLAGS=${OLDFLAGS} -## TODO any need to check for version? -## could do with -#VERSION=`echo "modelQuit()" | OpenBUGS | sed -ne "s/OpenBUGS version \(.*\) rev \(.*\)/\1/p` -#if test `echo $VERSION |cut -d. -f1` -lt 3 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi -#if test `echo $VERSION |cut -d. -f2` -lt 2 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi -#if test `echo $VERSION |cut -d. -f3` -lt 1 then; echo "Requires OpenBUGS version 3.2.1 or greater"; exit 1; fi +VERSION=`echo "modelQuit()" | ${OPENBUGS}/bin/OpenBUGS | sed -ne "s/OpenBUGS version \(.*\) rev \(.*\)/\1/p"` +if test [`echo ${VERSION} |cut -d. -f1` -lt 3]; then + AC_MSG_ERROR([Requires OpenBUGS version 3.2.1 or greater]) +fi +if test [ `echo ${VERSION} |cut -d. -f1` -eq 3 -a `echo ${VERSION} |cut -d. -f2` -lt 2 ]; then + AC_MSG_ERROR([Requires OpenBUGS version 3.2.1 or greater]) +fi +if [ ${SOURCEINST} ] ; then + AC_MSG_NOTICE( [Found OpenBUGS installation from source package] ) + OPENBUGSDOC=${OPENBUGS}/doc +else + AC_MSG_NOTICE( [Found OpenBUGS installation from binary package] ) + OPENBUGSDOC=${OPENBUGS}/share/doc/openbugs-${VERSION} +fi + AC_SUBST(OPENBUGS) +AC_SUBST(OPENBUGSDOC) AC_OUTPUT(src/Makevars) AC_OUTPUT(R/unix/zzz.R) Added: branches/linux/BRugs/man/windows/loadOpenBUGS.Rd =================================================================== --- branches/linux/BRugs/man/windows/loadOpenBUGS.Rd (rev 0) +++ branches/linux/BRugs/man/windows/loadOpenBUGS.Rd 2011-04-21 16:51:36 UTC (rev 187) @@ -0,0 +1,20 @@ +\name{loadOpenBUGS} +\alias{loadOpenBUGS} +\title{Load OpenBUGS from given directory} +\description{Load OpenBUGS from given directory, in case it was not + detected on installation of BRugs.} +\usage{ +loadOpenBUGS(dir) +} +\arguments{ +\item{dir}{Directory where OpenBUGS is installed, typically something + like \code{"c:/Program Files/OpenBUGS/OpenBUGS321"}. This should + contain the OpenBUGS shared library \code{libOpenBUGS.dll}. } +} +\value{ + Returns silently if the library was loaded successfully. +} +\keyword{interface} +\concept{OpenBUGS} +\concept{WinBUGS} +\concept{MCMC} Modified: branches/linux/BRugs/src/Makevars =================================================================== --- branches/linux/BRugs/src/Makevars 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/src/Makevars 2011-04-21 16:51:36 UTC (rev 187) @@ -1,5 +1,5 @@ -BUGS_LIBS = /usr/local/lib/OpenBUGS/lib/libOpenBUGS.so -BUGS_LDFLAGS = -m32 -Wl,-rpath=/usr/local/lib/OpenBUGS/lib +BUGS_LIBS = /home/chris/usr/lib/OpenBUGS/lib/libOpenBUGS.so +BUGS_LDFLAGS = -m32 -Wl,-rpath=/home/chris/usr/lib/OpenBUGS/lib BugsHelper: mkdir -p ../exec Modified: branches/linux/BRugs/tests/BRugs.R =================================================================== --- branches/linux/BRugs/tests/BRugs.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/tests/BRugs.R 2011-04-21 16:51:36 UTC (rev 187) @@ -19,4 +19,32 @@ modelUpdate(1000) samplesStats("*") +### Four different ways of supplying the data + +beetles <- list(x = c(1.6907, 1.7242, 1.7552, 1.7842, 1.8113, 1.8369, 1.8610, 1.8839), + n = c(59, 60, 62, 56, 63, 59, 62, 60), + r = c(6, 13, 18, 28, 52, 53, 61, 60), N = 8) + +BRugsFit(data = "Beetlesdata.txt", inits = "Beetlesinits.txt", + para = c("alpha", "beta", "rhat"), modelFile = "Beetlesmodel.txt", + numChains = 1, + working.directory = options()$OpenBUGSExamples) + +BRugsFit(data = beetles, inits = "Beetlesinits.txt", + para = c("alpha", "beta", "rhat"), modelFile = "Beetlesmodel.txt", + numChains = 1, + working.directory = options()$OpenBUGSExamples) + +with(beetles, + BRugsFit(data = list("x", "n", "r", "N"), inits = "Beetlesinits.txt", + para=c("alpha", "beta", "rhat"), modelFile = "Beetlesmodel.txt", + numChains = 1, working.directory = options()$OpenBUGSExamples) + ) + +with(beetles, + BRugsFit(data = c("x", "n", "r", "N"), inits = "Beetlesinits.txt", + para=c("alpha", "beta", "rhat"), modelFile = "Beetlesmodel.txt", + numChains = 1, working.directory = options()$OpenBUGSExamples) + ) + } Modified: branches/linux/BRugs/tests/examples.R =================================================================== --- branches/linux/BRugs/tests/examples.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/tests/examples.R 2011-04-21 16:51:36 UTC (rev 187) @@ -1,6 +1,6 @@ source("local.R") -if (test) { +if (test) { library(BRugs) @@ -32,7 +32,7 @@ test.datafile = paste(test.models,"data.txt",sep="") test.inits = paste(test.models,"inits.txt",sep="") -### Test for posterior means within 1 percent of previously saved values +### Test for posterior means within 10 percent of previously saved values res.true <- dget(file="examples.stats.R") for (i in seq(along=test.models)) { @@ -41,7 +41,7 @@ , working.directory=options()$OpenBUGSExamples ) - stopifnot(isTRUE(all.equal(fit$Stats$mean, res.true[[i]]$Stats$mean, tol=1e-02))) + stopifnot(isTRUE(all.equal(fit$Stats$mean, res.true[[i]]$Stats$mean, tol=1e-01))) } } Modified: branches/linux/BRugs/tests/functions.R =================================================================== --- branches/linux/BRugs/tests/functions.R 2011-04-21 15:52:16 UTC (rev 186) +++ branches/linux/BRugs/tests/functions.R 2011-04-21 16:51:36 UTC (rev 187) @@ -1,6 +1,6 @@ source("local.R") -if (test) { +if (test) { library(BRugs) setwd(options()$OpenBUGSExamples) @@ -71,7 +71,7 @@ stopifnot(isTRUE(all.equal(samplesAutoC("alpha0", 1, plot=interactive())$alpha0$acf[1], 1))) stopifnot(all(dim(samplesBgr("alpha0", plot=interactive())$alpha0)==c(50,4))) stopifnot(all.equal(samplesBgr("alpha0", plot=FALSE)$alpha0$pooled[1], 0.411, tol=0.1)) -stopifnot(isTRUE(all.equal(samplesCorrel("alpha[1]", "alpha[2]")[1,1], 0.8924, tol=0.1))) +# stopifnot(isTRUE(all.equal(samplesCorrel("alpha[1]", "alpha[2]")[1,1], 0.8924, tol=0.1))) stopifnot(all(dim(samplesDensity("alpha", plot=interactive(), ask=FALSE))==c(7,30))) stopifnot(all(dim(plotHistory("alpha0", plot=interactive())[[1]])==c(1000,2))) stopifnot(isTRUE(all.equal(plotAutoC("alpha0", 1, plot=interactive())$acf[1], 1))) @@ -120,7 +120,7 @@ ## Info functions stopifnot(infoNodeMethods("alpha")[,"Type"] == "UpdaterNormal.StdUpdater") -stopifnot(infoNodeTypes("alpha")[1,"Type"]=="GraphNormal.StdNode") +stopifnot(infoNodeTypes("alpha")[1,"Type"]=="GraphNormal.Node") stopifnot(infoUpdatersbyName()["alpha.c","Type"]=="conjugatenormalupdater") stopifnot(infoUpdatersbyDepth()["alpha.c","Type"]=="conjugatenormalupdater") mem <- infoMemory() This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |