[ESS-bugs] ess-beginning-of-function - bug in {R and S}-mode
Martin Maechler
maechler at stat.math.ethz.ch
Thu Jul 7 17:36:48 CEST 2005
>>>>> "StEgl" == Stephen Eglen <S.J.Eglen at damtp.cam.ac.uk>
>>>>> on Wed, 6 Jul 2005 10:15:20 +0100 writes:
>> C-M-a and C-M-e and all other ess-function-* commands fail
>> for things like
>>
>> myfun <-
>> ## bla1
>> ## bla2
>> ## bla3
>> ## bla4
>> function(x) {
>> .........
>> .........
>> }
>>
>> as long as your (point) is inside the '## bla.' comment lines
>>
>> John Chambers has been using this syntax extensively,
>> and actually S4 has defined that the '## bla?" lines are made
>> into a ``dummy help page'' as long as no real help page exists.
>> and IIRC, this even works in S-plus {but not in R}.
StEgl> sounds like a good way to get docstrings, in the same way that Emacs
StEgl> does at the top of a function definition! I'd have slightly prefered
StEgl> the look of something like:
StEgl> myfun <- function(x) {
StEgl> ## bla1
StEgl> ##...
StEgl> code
StEgl> }
I still prefer this -- quite a bit ---
StEgl> but if it is already in S and John C uses it, that's good enough for
StEgl> me to start thinking about changing. (Is it likely that R will adopt
StEgl> this convention for an informal doc string?)
This is really something that should be asked on R-devel;
or in particular to those in R-core who dare to fiddle with the
parser.
In R, currently, it does ``not really work''
because all the comments between "myfun" and " <- function(x)"
are lost as early as when *parsing* the things.
StEgl> I'm unlikely to get a chance to look at this soon, but will put it on
StEgl> my list of things to look at, as it sounds like a good thing to
StEgl> encourage documentation in this way.
I felt an urgency to look at our {beginning / end} of function
parsing, because when working with S4 methods and classes, the
current ESS behavior is really a bit painful for someone who is
used to
M-C-a M-C-e or Stephen's own "C-x n d" == narrow-to-defun
which can be used in ess mode as well :
Code like the following appears ``every where''
------------------------------------------------------------------------
setMethod("ranef", signature(object = "lmer"),
function(object, accumulate = FALSE, ...) {
val <- new("lmer.ranef",
lapply(.Call("lmer_ranef", object, PACKAGE = "Matrix"),
data.frame, check.names = FALSE),
varFac = object at bVar,
stdErr = .Call("lmer_sigma", object,
object at method == "REML", PACKAGE = "Matrix"))
if (!accumulate || length(val at varFac) == 1) return(val)
## check for nested factors
L <- object at L
if (any(sapply(seq(a = val), function(i) length(L[[Lind(i,i)]]@i))))
error("Require nested grouping factors to accumulate random effects")
val
})
------------------------------------------------------------------------
but we only get an error when the function boundaries are
sought.
I thought I had above case ("setMethod.....") almost working,
but ``not quite'' and
I am now seeing that the definitions for
ess-beginning-of-function
ess-end-of-function
in ess-mode.el where really geared to S3 and can hardly work
with other languages.
As a matter of fact:
They (and hence the C-M-a and C-M-e keys)
must fail completely since no "ess-function-pattern" is
defined for other ESS - languages
My fix would even more make these even more dependent on S (R || S-plus)..
...ugly...but I'd tend to commit that hack, since I really want something
working for myself when using setMethod(.), setGeneric(.), etc
all over the place.
After all, we have this in ess-cust.el
{just before the definition of
ess-R-function-pattern and ess-S-function-pattern
and I'm sure these used to be in ess-mode.el close to the
ess-beg/end-of-function definitions} :
;; FIXME : This is just for the S dialects; need to define this for others,
;; -----
;; {however "XLS-mode" should just use standard lisp "beginning of function"}
StEgl> Presumably this form of function definition also is not captured by
StEgl> the imenu code?
{I have to admit that I almost never use the imenu stuff}
----------
Martin
More information about the ESS-bugs
mailing list