[ESS] Easy argument list: r-autoyas

Ista Zahn izahn at psych.rochester.edu
Sat Mar 12 23:41:00 CET 2011


Dear Sven and Vitalie,
r-autoyas is fantastic. You've made me very happy, and I'm sure many
others feel the same. Thank you!

I'm actually running it as Vitalie suggested, (including binding
r-autoyas-expand to the "(" key) and it works quite well. I do have a
sort of feature request though; support for nested function calls. For
example:

dat <- data.frame(x=rnorm(10, mean=0, sd=1, row.names=NULL,
check.rows=FALSE, check.names=TRUE,
stringsAsFactors=default.stringsAsFactors()

OK, now imagine I've just finished typing 10 as the argument to rnorm.
I'd like to exit the rnorm yasnippet, but not the data.frame snippet.
I would also like to bind a function to exit the snippet to the ")"
key.

(defun r-autoyas-exit-snippet-delete-one ()
  "Exit this snippet."
  (interactive "*")
  (let ((deletefrom (point)))
    (ad-Orig-yas/abort-snippet)))

(define-key ess-mode-map (kbd ")")
  '(lambda () (interactive)
     (skeleton-pair-insert-maybe nil)
     (r-autoyas-exit-snippet-delete-one)))

But as you can probably tell I really don't know the first thing about
lisp. The above almost works, except that it doesn't delete the
remaining rnorm( arguments. I'd appreciate any tips for getting that
to work.

Thanks again, this is already an incredibly useful tool, especially
for functions with many arguments.

Best,
Ista
On Thu, Mar 10, 2011 at 5:40 PM, Sven Hartenstein
<lists at svenhartenstein.de> wrote:
> Hi Vitalie,
>
> great - looks like in you I finally found a lisp teacher! :-)
>
> Thanks very much for your ideas and (quick!) coding. I will find time
> on the weekend to try to understand it and update r-autoyas on my
> website.
>
> Best,
>
> Sven
>
>
> * Vitalie Spinu wrote:
>> Sven Hartenstein <lists at svenhartenstein.de> writes:
>>
>>
>> > Here is the code:
>> > http://www.svenhartenstein.de/Software/R-autoyas
>> >
>> > I'd love to receive your honest feedback!
>>
>> Hi Sven,
>>
>> A very nice attempt indeed. It can become a very useful addition to ESS.
>> One further step would be to have an option to scroll through methods
>> arguments, but that would take some considerable thinking.
>>
>> Here are a couple of points of how to improve on what you did. The complete
>> code follows.
>>
>> First, it would be probably more convenient if "(" key would directly invoke
>> the yas/expand. This is what I have in my .emacs:
>>
>> (define-key ess-mode-map (kbd "(") '(lambda () (interactive)
>>                                       (skeleton-pair-insert-maybe nil)
>>                                       (r-autoyas-expand nil t))))
>>
>> Second, it is nice to have C-g to delete all the remaining arguments (as
>> you've already suggested on your site). The easiest way I could find is to
>> advise yas/abort-snippet. Please see below.
>>
>> Third, it is inconvenient to maintain both .emacs and .Rprofile, one way of
>> avoiding it is to "inject" the necessary commands each time R-session starts
>> by means of ess-post-run-hook.
>>
>> This is the complete r-autoyas code which I have got in my .emacs:
>>
>> ;;;_ autoyas
>>
>> (defun r-autoyas-exit-snippet-delete-remaining ()
>>   "Exit yas snippet and delete the remaining argument list."
>>   (interactive "*")
>>   (let ((deletefrom (point)))
>>     (yas/exit-all-snippets)
>>     (delete-region deletefrom (point))))
>>
>> (defun r-autoyas-expand (&optional funname no-paren)
>>   "Insert argument list (in parentheses) of R function before the
>> point as intelligent yas snippets and expand the snippets."
>>   (interactive "*")
>>   (if (null funname)
>>       (setq funname (ess-r-args-current-function)))
>>   (ess-command (concat "r.autoyas.create('" funname "')\n")
>>                (get-buffer-create "*r-autoyas*"))
>>   (unless (null funname)
>>     (let (snippet)
>>       (with-current-buffer "*r-autoyas*"
>>         (if (< (length (buffer-string)) 10);; '[1] " "' if no valid fun
>>             (message "No valid function!")
>>           (delete-region 1 6)
>>           (goto-char (point-max))
>>           (delete-backward-char 2)
>>           (goto-char (point-min))
>>           (replace-string "\\\"" "\"")
>>           (goto-char (point-min))
>>           (replace-string "\\\\" "\\")
>>           (setq snippet (buffer-string))
>>           (when no-paren
>>             (setq snippet (substring snippet 1 -1)))
>>           ))
>>       (when snippet
>>         (yas/expand-snippet snippet)
>>         ))))
>>
>> (defun r-autoyas-inject-commands ()
>>   (process-send-string (get-process ess-current-process-name)
>>                        "r.autoyas.esc <- function(str) {
>>   str <- gsub('$', '\\\\$', str, fixed=TRUE)
>>   str <- gsub('`', '\\\\`', str, fixed=TRUE)
>>   return(str)
>>   };
>>   r.autoyas.create <- function(funname) {
>>   if (!existsFunction(funname)) return(' ')
>>   formals <- formals(funname)
>>   nr <- 0
>>   closebrackets <- 0
>>   str <- NULL
>>   for (field in names(formals)) {
>>   type <- typeof(formals[[field]])
>>   if (type=='symbol' & field!='...') {
>>   nr <- nr+1
>>   str <- append(str, paste(', ${',nr,':',field,'}', sep=''))
>>   } else if (type=='symbol' & field=='...') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ${',nr,':',field,'}}', sep=''))
>>   } else if (type=='character') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ',field,'=${',nr,':\\'',gsub('\\'', '\\\\\\'', r.autoyas.esc(encodeString(formals[[field]])), fixed=TRUE),'\\'}}', sep=''))
>>   } else if (type=='logical') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ',field,'=${',nr,':',as.character(formals[[field]]),'}}', sep=''))
>>   } else if (type=='double') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ',field,'=${',nr,':',as.character(formals[[field]]),'}}', sep=''))
>>   } else if (type=='NULL') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ',field,'=${',nr,':NULL}}', sep=''))
>>   } else if (type=='language') {
>>   nr <- nr+2
>>   str <- append(str, paste('${',nr-1,':, ',field,'=${',nr,':',r.autoyas.esc(deparse(formals[[field]])),'}}', sep=''))
>>   }
>>   }
>>   str <- paste(str, sep='', collapse='')
>>   if (grepl(', ', str, fixed=TRUE)) str <- sub(', ', '', str) # remove 1st ', ' (from 1st field)
>>   str <- paste('(',str,')', sep='')
>>   str
>>   }\n")
>>   )
>>
>>
>> (defadvice yas/abort-snippet (around r-delete-remaining)
>>   (if (member major-mode '(ess-mode inferior-ess-mode))
>>       (r-autoyas-exit-snippet-delete-remaining)
>>     ad-do-it)
>>   )
>>
>> (ad-activate 'yas/abort-snippet)
>> (add-hook 'ess-post-run-hook 'r-autoyas-inject-commands)
>>
>> (define-key ess-mode-map (kbd "C-M-<tab>")
>>   '(lambda ()(interactive)(r-autoyas-expand nil t)))
>>
>> (define-key ess-mode-map (kbd "(") '(lambda () (interactive)
>>                                       (skeleton-pair-insert-maybe nil)
>>                                       (r-autoyas-expand nil t)))
>>
>>
>> Best,
>> Vitalie.
>>
>> >
>> > Sven
>> >
>> > ______________________________________________
>> > ESS-help at r-project.org mailing list
>> > https://stat.ethz.ch/mailman/listinfo/ess-help
>
> ______________________________________________
> ESS-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/ess-help
>



-- 
Ista Zahn
Graduate student
University of Rochester
Department of Clinical and Social Psychology
http://yourpsyche.org



More information about the ESS-help mailing list