Michael Lapsley was suggesting on R-help direct copies to gif/png/jpeg.
The following seems to do a sensible job for me of copying the current
device to any bitmap format supported by gs. The manipulation is needed
to work around assumptions made by postscript(), and I think better fixed
in postscript() (but not a couple of days before a release).
I want to make onefile=FALSE work on postscript() (it needs to start
a file for each page, and give it a EPSF-3.0 header), and to allow
user-specified paper sizes and the option of not centring on the page.
Oh, and I do know it is gswin32c on Windows: that is easy to incorporate
but I have not tested it.
One could attempt to retrieve height and width from the current device,
but I don't see that information is presently available from R code.
Any comments?
dev2bitmap <- function(file, type="png256", height=6, width=6,
res=72,
                      pointsize, ...)
{
    rc <- system("gs -help > /dev/null")
    if(rc != 0) stop("Sorry, gs cannot be found")
    gs <- system("gs -help", intern=TRUE)
    st <- grep("^Available", gs)
    en <- grep("^Search", gs)
    gs <- gs[(st+1):(en-1)]
    devs <- c(strsplit(gs, " "), recursive=T)
    if(match(type, devs, 0) == 0)
        stop(paste(paste("Device ", type, "is not
available"),
                   "Available devices are",
                   paste(gs, collapse="\n"), sep="\n"))
    if(missing(pointsize)) pointsize <- 1.5*min(width, height)
    tmp <- tempfile("Rbit")
    on.exit(unlink(tmp))
    dev.print(device=postscript, file=tmp, width=width,
              height=height, pointsize=pointsize, horizontal=F, ...)
    psfile <- scan(tmp, what="", sep="\n", quiet=TRUE)
    bb <- strsplit(psfile[9], " ")[[1]]
    ep <- grep("^%%EndProlog", psfile)
    unlink(tmp)
    tmp2 <- tempfile("Rbit")
    on.exit(unlink(tmp2))
    cat(psfile[1:ep], file=tmp2, sep="\n")
    cat(paste("-",bb[2], " -", bb[3], "
translate\n", sep=""),
        file=tmp2, append=TRUE)
    cat(psfile[(ep+1):length(psfile)], file=tmp2, sep="\n",
append=TRUE)
    cmd <- paste("gs -dNOPAUSE -dBATCH -q -sDEVICE=", type,
                 " -r", res,
                 " -g", ceiling(res*width), "x",
ceiling(res*height),
                 " -sOutputFile=", file, " ", tmp2,
sep="")
    system(cmd)
    invisible()
}
-- 
Brian D. Ripley,                  ripley@stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272860 (secr)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-devel 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-devel-request@stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._