Hello, First, regarding GeSHi syntax highlighting for R, I have done one for the R Wiki (plus the R function that generates the list of keywords automatically). I will attach it to a second email send privately to you, since the mailing list do not accept attachments.
For the problem of keeping web pages up-to-date with R code, I am also considering this problem with the R Wiki. Although I still do not have a completely working solution, the approach is similar to Sweave. I have a function which extracts the R code from wiki pages (that is, it 'Stangles' the wiki page, in the Sweave terminology). I can get, thus, the R code from all wiki pages in turn, test them and write a report with a couple of R code lines. Here is are my functions: getWikiRcode <- function(wikipage, url = "http://wiki.r-project.org/rwiki", strip.empty.lines = TRUE, strip.output = FALSE) { # Read the raw wiki page Url <- paste(url, "/doku.php?id=", wikipage, "&do=export_raw", sep ="") Raw <- readLines(Url) # Get only <code r> .... </code> chunks from this page Codestart <- grep("^\\s*<code", Raw) Codeend <- grep("^\\s*</code>", Raw) # A little bit of checking first if (length(Codestart) != length(Codeend) || any(Codeend <= Codestart)) stop("Malformed wiki page (wrong <code>... </code> sections)") # Get only r code sections (those starting with <code r> from the list Rstart <- grep("^\\s*<code r>", Raw) if (length(Rstart) == 0) return(character(0)) # no R code in this page isRsection <- Codestart %in% Rstart Rend <- Codeend[isRsection] # Construct the list of text lines related to r code R <- data.frame(Start = Rstart, End = Rend) Seq <- function(x) seq(from = x[1], to = x[2]) Rrows <- c(apply(R, 1, Seq), recursive = TRUE) Rcode <- Raw[Rrows] # Eliminate <code r> and </code> tags Rcode <- gsub("^\\s*</?code( r)?>.*$", "", Rcode) # Eliminate prompt from R code '> ', or '+ ' at the begining of a line Rcode <- sub("^[>+] ", "", Rcode) # Possibly eliminate empty lines if (strip.empty.lines) Rcode <- Rcode[Rcode != ""] # Possibly eliminate output (lines starting with '#!') if (strip.output) { Routput <- grep("^\\#\\!", Rcode) if (length(Routput) > 0) Rcode <- Rcode[-Routput] } # Return the R code return(Rcode) } rcode <- getWikiRcode("tips:data-frames:merge") rcode sourceWikiRcode <- function(wikipage, echo = TRUE, url = "http://wiki.r-project.org/rwiki", strip.empty.lines = TRUE, strip.output = FALSE, ...) { # Call getWikiRcode() to extract r code from wiki pages Rcode <- getWikiRcode(wikipage = wikipage, url = url, strip.empty.lines = strip.empty.lines, strip.output = strip.output) if (length(Rcode) == 0) { warning("No r code in this page!") } else { Con <- textConnection(Rcode) source(Con, echo = echo, ...) close(Con) } } sourceWikiRcode("tips:data-frames:merge") # Here, the last part of this page is not directly executable (data1 is not defined) # but the rest is fine! This is suboptimal, and I am considering rewriting it in PHP to return R code only from the wiki server. Best, Philippe Grosjean Gavin Simpson wrote: > On Sat, 2007-01-06 at 10:58 -0500, Gabor Grothendieck wrote: >> The arguments to the functions can differ too even if they >> exist on multiple platforms. system() on Windows has the >> input= argument but not on UNIX. > > That's a good point Gabor, and one I hadn't considered as yet. As I'm > only just setting out on the road to providing R help resources for the > wider world (rather than the limited environs of the courses I have > run), I tend to not have thought about these things much - though I > guess I have a few gotchas waiting to bite me in the ass before too > long. > > I am just starting to think about the best way to organise the snippets > of code to allow me to keep them up-to-date with current R and changes > in package code that the snippets use. Dropping the code verbatim into > PHP scripts isn't a good idea. At the moment I intend to store all > snippets in individual *.R files and read them into to variables within > the PHP scripts, from where they will be highlighted and formatted for > display. > > It would be reasonably easy to write an R script to source all *.R files > in a directory to look for errors and problems. And having them all as > separate files means I can still use Emacs/ESS to prepare, format, and > run the code through R, which is my preferred environment. > > All the best, > > G > >> On 1/6/07, Duncan Murdoch <[EMAIL PROTECTED]> wrote: >>> On 1/6/2007 9:25 AM, Gavin Simpson wrote: >>>> On Sat, 2007-01-06 at 13:48 +0000, Prof Brian Ripley wrote: >>>>> Could you tell us what you mean by >>>> Thank you for your reply, Prof. Ripley. >>>> >>>>> - 'function' (if() and + are functions in R, so do you want those?) >>>> I was thinking about functions that are used like this: foo() >>>> So I don't need things like "names<-". I don't need functions like +. -, >>>> $, as I can highlight the separately if desired, though I'm not doing >>>> this at the moment. >>>> >>>> Functions like for() while(), if() function() are handled separately. >>>> >>>>> - 'a base R installation'? What is 'base R' (standard + recommended >>>>> packages?) And on what platform: the list is platform-specific? >>>> Yes, I mean standard + recommended packages. As for platform, most of my >>>> intended audience will be MS Windows users, though I am using Linux >>>> (Fedora) to generate this list (i.e. my R installation is on Linux). >>> Be careful: the installed list of functions differs slightly from >>> platform to platform. For example, on Windows there's a function >>> choose.dir in the utils package, but I don't think this exists on Unix. >>> >>> The list also varies from version to version, so if you could manage to >>> run some code in the user's installed R to generate the list on the fly, >>> you'd get the most accurate list. >>> >>> Duncan Murdoch >>> >>>>> Here is a reasonable shot: >>>>> >>>>> findfuns <- function(x) { >>>>> if(require(x, character.only=TRUE)) { >>>>> env <- paste("package", x, sep=":") >>>>> nm <- ls(env, all=TRUE) >>>>> nm[unlist(lapply(nm, function(n) exists(n, where=env, >>>>> mode="function", >>>>> inherits=FALSE)))] >>>>> } else character(0) >>>>> } >>>>> pkgs <- dir(.Library) >>>>> z <- lapply(pkgs, findfuns) >>>>> names(z) <- pkgs >>>> Excellent, that works just fine for me. I can edit out certain packages >>>> that I don't expect to use, before formatting as desired. I can also use >>>> this function on a library of packages that I use regularly and will be >>>> using in the web pages. >>>> >>>>> I don't understand your desired format, but >>>>> >>>>> write(sQuote(sort(unique(unlist(z)))), "") >>>> I wanted a single string "...", with entries enclosed in "''" and >>>> separated by "," (this is to go in a PHP array). I can generate such a >>>> string from your z, above, as follows: >>>> >>>> paste(sQuote(sort(unique(unlist(z)), decreasing = TRUE)), >>>> collapse = ", ") >>>> >>>>> gives a single-column quoted list. It does include internal functions, >>>>> operators, S3 methods ... so you probably want to edit it. >>>> Once again, thank you. >>>> >>>> All the best >>>> >>>> Gav >>>> >>>>> On Sat, 6 Jan 2007, Gavin Simpson wrote: >>>>> >>>>>> Dear List, >>>>>> >>>>>> I'm building an R syntax highlighting file for GeSHi [*] for a website I >>>>>> am currently putting together. The syntax file needs a list of keywords >>>>>> to highlight. How can I generate a list of all the functions in a base R >>>>>> installation? >>>>>> >>>>>> Ideally the list would be formatted like this: >>>>>> >>>>>> "'fun1', 'fun2', 'fun3'" >>>>>> >>>>>> when printed to the screen so I can copy and paste it into the syntax >>>>>> file. >>>>>> >>>>>> I'm sure this has been asked before, but I stupidly didn't save that >>>>>> email and I couldn't come up with a suitable query parameter for >>>>>> Jonathan Baron's search site to return results before timing out. >>>>>> >>>>>> Thanks in advance, >>>>>> >>>>>> Gav >>>>>> >>> ______________________________________________ >>> [email protected] mailing list >>> https://stat.ethz.ch/mailman/listinfo/r-help >>> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html >>> and provide commented, minimal, self-contained, reproducible code. >>> >> ______________________________________________ >> [email protected] mailing list >> https://stat.ethz.ch/mailman/listinfo/r-help >> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html >> and provide commented, minimal, self-contained, reproducible code. ______________________________________________ [email protected] mailing list https://stat.ethz.ch/mailman/listinfo/r-help PLEASE do read the posting guide http://www.R-project.org/posting-guide.html and provide commented, minimal, self-contained, reproducible code.
