[R] bootstrap: boot package
Ben Bolker
ben at zoo.ufl.edu
Thu Jan 31 17:43:34 CET 2002
I've basically done this (although entirely in R rather than using
Perl); see attached.
(Frank Harrell reported a problem with an earlier version of this, so
I'm attaching the latest. It seems to work OK on my system with
--vanilla).
Basically,
source(...)
create.index.CRAN()
help.search.CRAN("foo")
should work.
Improvements welcome.
On Mon, 28 Jan 2002, Dirk Eddelbuettel wrote:
> IIRC one problem is help.search() on one's computer is "local", it cannot
> know about packages which are not installed. So would it be a) feasible and
> b) desirable to create a "meta"-package for nothing but "global"
> documentation searches ? One way would be to go online and query Jon Baron's
> search engine, another to work offline by searching a db-in-a-file of
> keywords stripped from the documentation on a CRAN master [ feeding this
> could be automated with Perl scripts ]
>
> Am I making sense, or do I need more coffee?
>
> Dirk
>
download.index.CRAN <- function(pkg,CRAN=getOption("CRAN"),
descrip=paste(srccontrib.url(CRAN),"/Descriptions",sep=""),
local.ext=".INDEX.tmp") {
download.file(paste(descrip,"/",pkg,".INDEX",sep=""),
paste(pkg,local.ext,sep=""))
}
srccontrib.url <- function(CRAN) {
paste(CRAN,"/src/contrib",sep="")
}
## these two functions are duplicated from bbfuns package:
## didn't want to introduce dependence for minor utility functions
## strsplit produces zero-length words if there are leading spaces
nwords <- function(x) {
sapply(strsplit.words(x),function(z)length(z[nchar(z)>0]))
}
strsplit.words <- function(x) {
strsplit(gsub("[ \t]*"," ",x)," ")
}
## readline() without the 32-char limit
## [unnecessary with more recent R versions??]
myreadline <- function(prompt="") {
cat(prompt)
readLines(n=1)
}
trans.index.CRAN <- function(fn) {
## cat(fn,"\n")
lines <- scan(fn,what=character(),sep="\n",quiet=TRUE)
ret <- NULL
if (length(lines)>0) {
## paste continuation lines together
## look for initial whitespace; might miss funny formats
tablines <- grep("^[ \t]",lines)
lines <- sub("^[\t ]*","",lines) ## now delete initial whitespace
## join "continuation sets" (sets of consecutive lines with leading whitespace)
if (length(tablines)>0) {
v <- 1:length(lines)
csets <- v-cumsum(v %in% tablines)
lines <- sapply(split(lines,csets),paste,collapse=" ")
}
pkgname <- gsub("/INDEX","",gsub("[\* ]*","",lines[1]))
lines <- lines[-1]
pkg <- rep(pkgname,length(lines))
fun <- sapply(strsplit.words(lines),"[",1)
descr <- sapply(strsplit.words(lines),function(z)paste(z[-1],collapse=" "))
ret <- cbind(pkg,fun,descr)
dimnames(ret) <- list(NULL,c("Package","Function","Description"))
}
ret
}
create.index.CRAN <- function(CRAN=getOption("CRAN"),
contriburl=srccontrib.url(CRAN),
descrip=paste(srccontrib.url(CRAN),"/Descriptions",sep=""),
local.ext=".INDEX.tmp",
save=TRUE,savefile="CRAN-index.RData",
download=TRUE) {
if (download) {
pkglist <- CRAN.packages(contriburl=contriburl)
sapply(pkglist[,1],download.index.CRAN,CRAN=CRAN,descrip=descrip,
local.ext=local.ext)
}
indfiles <- list.files(pattern=paste("*",local.ext,sep=""))
CRAN.index <- do.call("rbind",lapply(indfiles,trans.index.CRAN))
answer <- substr(myreadline("Delete temporary index files (y/N)? "), 1, 1)
if (answer == "y" | answer == "Y")
unlink(indfiles, TRUE)
if (save) save(CRAN.index,file=savefile)
invisible(CRAN.index)
}
help.search.CRAN <- function(str,indexmat=CRAN.index,ignore.case=TRUE,
packages.only=FALSE,
load=TRUE,
file="CRAN-index.RData") {
## check for object/file, load if possible
if (!exists(deparse(substitute(indexmat)))) {
if (load) {
if (!file.exists(file))
stop("Can't find CRAN index file to load (try create.index.CRAN)")
load(file)
}
else stop ("Can't find CRAN index object (try loading from a file?)")
}
## find matches in either Function or Description fields
ind <- unique(c(grep(str,indexmat[,"Function"],ignore.case=ignore.case),
grep(str,indexmat[,"Description"],ignore.case=ignore.case)))
if (length(ind)==0)
cat("No functions found\n")
else
if (packages.only) noquote(unique(indexmat[ind,"Package"]))
else noquote(indexmat[ind,])
}
## junk in index: PTAk (how to filter?)
## give "no functions found" message ?
--
318 Carr Hall bolker at zoo.ufl.edu
Zoology Department, University of Florida http://www.zoo.ufl.edu/bolker
Box 118525 (ph) 352-392-5697
Gainesville, FL 32611-8525 (fax) 352-392-3704
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !) To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._
More information about the R-help
mailing list