unofficial mirror of emacs-devel@gnu.org 
 help / color / mirror / code / Atom feed
* macros and the lexical environment
@ 2013-06-04 21:48 Nic Ferrier
  2013-06-04 23:07 ` Pascal J. Bourguignon
                   ` (2 more replies)
  0 siblings, 3 replies; 9+ messages in thread
From: Nic Ferrier @ 2013-06-04 21:48 UTC (permalink / raw)
  To: emacs-devel

A while ago I wrote to the list about s-lex-format, a contribution I
made to magnars excellent s library for string handling.

s-lex-format is designed to let you interpolate values from the current
lexical environment into a string, like this:

  (let ((v 42)
        (a "hello world"))
     (s-lex-format "${a} - the answer is ${v}"))

this is terrifically useful.

However. It's implementation is a pain. I went backwards and forwards
with a dynamic version that looked up the specified values by name,
either by using symbol-value or peeking inside lexical binding (capture
a lambda, look in the closure's list of bindings).

I decided that it would be better to expand the format string into a
list of variable references. But that doesn't work well unless the
string is static, using a reference for the format string doesn't work
because it's not available at compile time:

  (let ((v 42)
        (a "hello world")
        (template "${a} - the answer is ${v}"))
     (s-lex-format template))

will fail to expand.

I'm going to have to go back to getting the dynamic version working for
now.

But what I'm really asking is, isn't this quite a useful thing to want
to do? get at the current environment state? the interpreter must know
the environment state. Could it be exposed to macros at compile time?
Perhaps through some function that returns an alist? or a function with
a symbol-name like interface?

Thoughts?



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-04 21:48 macros and the lexical environment Nic Ferrier
@ 2013-06-04 23:07 ` Pascal J. Bourguignon
  2013-06-05  8:23   ` Nic Ferrier
  2013-06-05  1:48 ` Stefan Monnier
  2013-06-05 20:34 ` Dmitry Gutov
  2 siblings, 1 reply; 9+ messages in thread
From: Pascal J. Bourguignon @ 2013-06-04 23:07 UTC (permalink / raw)
  To: emacs-devel

Nic Ferrier <nferrier@ferrier.me.uk> writes:

> A while ago I wrote to the list about s-lex-format, a contribution I
> made to magnars excellent s library for string handling.
>
> s-lex-format is designed to let you interpolate values from the current
> lexical environment into a string, like this:
>
>   (let ((v 42)
>         (a "hello world"))
>      (s-lex-format "${a} - the answer is ${v}"))
>
> this is terrifically useful.
>
> However. It's implementation is a pain. 


???

(defmacro s-lex-format (string)
  (s-lex-format* string))

Is that painful???

The most painful in your s-lex-format, it's the $ before the brace!



(defmacro s-lex-format (string)
  (s-lex-format* string))

(defun s-lex-format* (string)
  (loop
     with last = 0
     with arguments = '()
     with result = ""
     for start = (search "${" string) then (search "${" string :start2 last)
     while start
     do (let ((end (search "}" string :start2 start)))
          (unless end (error "Missing } after ${"))
          (push (intern (subseq string (+ 2 start) end)) arguments)
          (setf result (format "%s%s%%s" result (subseq string last start))
                last (1+ end)))
     finally (let ((end (length string)))
               (return `(format ,(concat result (subseq string last end))
                                ,@(nreverse arguments))))))


(s-lex-format*  "${a} - the answer is ${v}")
--> (format "%s - the answer is %s" a v)


(byte-compile '(lambda ()
                (let ((v 42)
                      (a "hello world"))
                  (s-lex-format "${a} - the answer is ${v}"))))
--> #[nil "\302\303^X^Y\304\305^H #*\207" 
          [a v 42 "hello world" format "%s - the answer is %s"]
          4]






> But what I'm really asking is, isn't this quite a useful thing to want
> to do? get at the current environment state? the interpreter must know
> the environment state. 

By definition, the lexical state is lexical, therefore you know it, even
before writing the s-lex-format expression!


> Could it be exposed to macros at compile time?

It could, but it's not necessary.


Otherwise, the principle of lisp is to use fully parenthesized prefix
notation.  Therefore don't try to subvert it by accessing
subreptitiously the lexical environment.  Instead, just define your own
macros.   For example, to pass the "lexical environment" to the
run-time:


(defmacro with-variable-memo-let (memo bindings &rest body)
  (let ((vars (mapcar (lambda (binding)
                        (if (atom binding) binding (first binding)))
                      bindings)))
    `(let ((,memo ',vars)
           ,@bindings)
       ,@body)))

(with-variable-memo-let memo
  ((v 42)
   (a "hello world"))
  memo)
--> (v a)


-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
A bad day in () is better than a good day in {}.
You can take the lisper out of the lisp job, but you can't take the lisp out
of the lisper (; -- antifuchs




^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-04 21:48 macros and the lexical environment Nic Ferrier
  2013-06-04 23:07 ` Pascal J. Bourguignon
@ 2013-06-05  1:48 ` Stefan Monnier
  2013-06-05 20:34 ` Dmitry Gutov
  2 siblings, 0 replies; 9+ messages in thread
From: Stefan Monnier @ 2013-06-05  1:48 UTC (permalink / raw)
  To: Nic Ferrier; +Cc: emacs-devel

>   (let ((v 42)
>         (a "hello world")
>         (template "${a} - the answer is ${v}"))
>      (s-lex-format template))

> will fail to expand.

Sounds fair: lexical scoping basically means that variables don't really
have a name (the name is just a way to make it easy for the programmer to
specify which use corresponds to which variable declaration).

If you want to be able to share templates, then you can do:

   (let ((v 42)
         (a "hello world")
         (template (lambda () (s-lex-format "${a} - the answer is ${v}"))))
      (funcall template))

> to do? get at the current environment state? the interpreter must know
> the environment state.

Which interpreter?  The byte-code interpreter knows the state, but not
the names, which have been thrown away during byte-compilation.

> Could it be exposed to macros at compile time?

What would "it" be, exactly?

I mean: yes we could theoretically provide to macros some info about the
lexical environment, tho it couldn't be much more than "here is the list
of variables in the current lexical environment".

What would you use it for?


        Stefan



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-04 23:07 ` Pascal J. Bourguignon
@ 2013-06-05  8:23   ` Nic Ferrier
  2013-06-05  8:35     ` Jambunathan K
  2013-06-05 21:08     ` Pascal J. Bourguignon
  0 siblings, 2 replies; 9+ messages in thread
From: Nic Ferrier @ 2013-06-05  8:23 UTC (permalink / raw)
  To: Pascal J. Bourguignon; +Cc: emacs-devel

Nic Ferrier said:

>> However. It's implementation is a pain. 

"Pascal J. Bourguignon" <pjb@informatimago.com> replied:

> ???
>
> (defmacro s-lex-format (string)
>   (s-lex-format* string))
>
> Is that painful???
>
> The most painful in your s-lex-format, it's the $ before the brace!
>
> (defmacro s-lex-format (string)
>   (s-lex-format* string))
>
> (defun s-lex-format* (string)
>   (loop
>      with last = 0
>      with arguments = '()
>      with result = ""
>      for start = (search "${" string) then (search "${" string :start2 last)
>      while start
>      do (let ((end (search "}" string :start2 start)))
>           (unless end (error "Missing } after ${"))
>           (push (intern (subseq string (+ 2 start) end)) arguments)
>           (setf result (format "%s%s%%s" result (subseq string last start))
>                 last (1+ end)))
>      finally (let ((end (length string)))
>                (return `(format ,(concat result (subseq string last end))
>                                 ,@(nreverse arguments))))))
>
>
> (s-lex-format*  "${a} - the answer is ${v}")
> --> (format "%s - the answer is %s" a v)
>
>
> (byte-compile '(lambda ()
>                 (let ((v 42)
>                       (a "hello world"))
>                   (s-lex-format "${a} - the answer is ${v}"))))
> --> #[nil "\302\303^X^Y\304\305^H #*\207" 
>           [a v 42 "hello world" format "%s - the answer is %s"]
>           4]

Fantastic. If only you had read all my mail because I went on to say:


>> I decided that it would be better to expand the format string into a
>> list of variable references. But that doesn't work well unless the
>> string is static, using a reference for the format string doesn't
>> work because it's not available at compile time:
>>
>>  (let ((v 42)
>>        (a "hello world")
>>        (template "${a} - the answer is ${v}"))
>>     (s-lex-format template))
>>
>> will fail to expand.

and yours suffers from the same problem of course.


> Otherwise, the principle of lisp is to use fully parenthesized prefix
> notation.  Therefore don't try to subvert it by accessing
> subreptitiously the lexical environment.  Instead, just define your own
> macros.   For example, to pass the "lexical environment" to the
> run-time:
>
>
> (defmacro with-variable-memo-let (memo bindings &rest body)
>   (let ((vars (mapcar (lambda (binding)
>                         (if (atom binding) binding (first binding)))
>                       bindings)))
>     `(let ((,memo ',vars)
>            ,@bindings)
>        ,@body)))
>
> (with-variable-memo-let memo
>   ((v 42)
>    (a "hello world"))
>   memo)
> --> (v a)

/me feels lectured at.

The point of the macro was clear, to let the user avoid repeating
themselves.

I agree that a Lisp syntax is nearly always best, however, this is a
good exception. A string syntax is useful to mix in data in other
formats than s-expressions (HTML for example, although another way of
doing this would be to switch everything to s-expressions like esxml
does). String stuff is also easy to adapt to buffers so s-lex-format
was easy to adapt to buffers.

In summary, you haven't resolved the problem, it's fundamental in
elisp. You can't get at the names of the variables in scope at compile
time and have:

* variables references for the template
* or a compiled version


Nic



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-05  8:23   ` Nic Ferrier
@ 2013-06-05  8:35     ` Jambunathan K
  2013-06-05 21:08     ` Pascal J. Bourguignon
  1 sibling, 0 replies; 9+ messages in thread
From: Jambunathan K @ 2013-06-05  8:35 UTC (permalink / raw)
  To: Nic Ferrier; +Cc: Pascal J. Bourguignon, emacs-devel


The discussion altogether is whizzing past my head.  

As an eaves dropper, I am reminded of `byte-compile-bound-variables'.
Search for it in compile.el.



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-04 21:48 macros and the lexical environment Nic Ferrier
  2013-06-04 23:07 ` Pascal J. Bourguignon
  2013-06-05  1:48 ` Stefan Monnier
@ 2013-06-05 20:34 ` Dmitry Gutov
  2013-06-05 22:41   ` Stefan Monnier
  2 siblings, 1 reply; 9+ messages in thread
From: Dmitry Gutov @ 2013-06-05 20:34 UTC (permalink / raw)
  To: Nic Ferrier; +Cc: emacs-devel

Nic Ferrier <nferrier@ferrier.me.uk> writes:
> I decided that it would be better to expand the format string into a
> list of variable references. But that doesn't work well unless the
> string is static, using a reference for the format string doesn't work
> because it's not available at compile time:
>
>   (let ((v 42)
>         (a "hello world")
>         (template "${a} - the answer is ${v}"))
>      (s-lex-format template))
>
> will fail to expand.

Let me point out that this also is not supported in all languages that I
know that support this kind of string interpolation natively (i.e. Ruby
and CoffeScript). And for dynamically generated templates, you'll always
have `format'.

> But what I'm really asking is, isn't this quite a useful thing to want
> to do? get at the current environment state? the interpreter must know
> the environment state. Could it be exposed to macros at compile time?

Somewhat relatedly, I'd really like to see `debug' and `edebug' support
local variable evaluation in lexical scoping environment. Apparently,
it's rather hard to implement.



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-05  8:23   ` Nic Ferrier
  2013-06-05  8:35     ` Jambunathan K
@ 2013-06-05 21:08     ` Pascal J. Bourguignon
  1 sibling, 0 replies; 9+ messages in thread
From: Pascal J. Bourguignon @ 2013-06-05 21:08 UTC (permalink / raw)
  To: emacs-devel

Nic Ferrier <nferrier@ferrier.me.uk> writes:

> Nic Ferrier said:
>
>>> However. It's implementation is a pain. 
>
> "Pascal J. Bourguignon" <pjb@informatimago.com> replied:
>
>> ???
>>> I decided that it would be better to expand the format string into a
>>> list of variable references. But that doesn't work well unless the
>>> string is static, using a reference for the format string doesn't
>>> work because it's not available at compile time:
>>>
>>>  (let ((v 42)
>>>        (a "hello world")
>>>        (template "${a} - the answer is ${v}"))
>>>     (s-lex-format template))
>>>
>>> will fail to expand.
>
> and yours suffers from the same problem of course.

Indeed, I didn't read closely the end of your message, that's what a
java work day does to your brain :-(

> In summary, you haven't resolved the problem, it's fundamental in
> elisp. You can't get at the names of the variables in scope at compile
> time and have:

Now, as I said in my previous answer, you can do the book-keeping
yourself.  This means, define macros to use instead of defun, lambda,
let, let*, etc.   In Common Lisp it's a simple matter, shadowing
CL:DEFUN etc, and defining macros named DEFUN, etc, in whatever other
package.

Since we don't have packages in emacs, we'll have to use different
names, for example, edefun, elambda, elet, elet*, etc. (Or one could
spend some time to hack obarrays into real CL-like packages, but I doubt
it would be accepted by emacs maintainers, given the ostracism 'cl is
victim of.

Anyways:


(eval-when (compile load eval)
  (defun split-body (body)
    (let ((docstring    (when (and (stringp (first body))
                                   (rest body))
                          (list (pop body))))
          (declarations (loop
                           while (and body
                                      (listp (first body))
                                      (assoc (first (first body)) defun-declarations-alist))
                           collect (pop body))))
      (list docstring declarations body)))

  (defun arglist-parameter-names (arglist)
    (set-difference arglist '(&optional &rest))))


(defvar *environment* '())

(defmacro elambda (arglist &rest docstring-decl-body)
  (let ((variables (arglist-parameter-names arglist)))
    (destructuring-bind (docstring declarations body) (split-body docstring-decl-body)
      `(lambda ,arglist
         ,@docstring
         ,@declarations
         (let ((*environment* (append ',variables *environment*)))
           ,@body)))))

(defmacro edefun (name arglist &rest docstring-decl-body)
  (let ((variables (arglist-parameter-names arglist)))
   (destructuring-bind (docstring declarations body) (split-body docstring-decl-body)
     `(defun ,name ,arglist
        ,@docstring
        ,@declarations
        (let ((*environment* (append ',variables *environment*)))
          ,@body)))))

(defmacro elet (varlist  &rest body)
  (let ((variables (mapcar (lambda (binding) (if (atom binding) binding (first binding)))
                           varlist)))
    `(let ((*environment* (append ',variables *environment*)))
       (let ,varlist 
         ,@body))))

(defmacro elet* (varlist  &rest body)
  (let ((variables (mapcar (lambda (binding) (if (atom binding) binding (first binding)))
                           varlist)))
    `(let ((*environment* (append ',variables *environment*)))
       (let* ,varlist 
         ,@body))))


(defun s-lex-format* (string environment)
  (loop
     with last = 0
     with arguments = '()
     with result = ""
     for start = (search "${" string) then (search "${" string :start2 last)
     while start
     do (let ((end (search "}" string :start2 start)))
          (unless end (error "Missing } after ${"))
          (push (intern (subseq string (+ 2 start) end)) arguments)
          (setf result (format "%s%s%%s" result (subseq string last start))
                last (1+ end)))
     finally (let* ((end (length string))
                    (format-control (concat result (subseq string last end)))
                    (undefined (list 'undefined))
                    (values (mapcar (lambda (variable)
                                      (let ((value (getf environment variable undefined)))
                                        (when (eq value undefined)
                                          (error "Undefined variable %s" variable))
                                        value))
                                    (nreverse arguments))))
               (return (apply (function format) format-control values))))))

(defmacro s-lex-format (string-expression)
  `(s-lex-format* ,string-expression
                  (list ,@(mapcan (lambda (variable)
                                    (list `',variable variable))
                                  *environment*))))

(elet ((v 42)
       (a "hello world"))
   (s-lex-format "${a} - the answer is ${v}"))
--> "hello world - the answer is 42"

(let ((control-string "${a} - the answer is ${v}"))
  (elet ((v 42)
         (a "hello world"))
        (s-lex-format control-string)))
--> "hello world - the answer is 42"



In general, there's an advantage to proceed this way, in that you can
disclose explicitely the lexical environment you want to publish:

(let ((control-string "${a} / ${private}- the answer is ${v}"))
  (elet ((v 42)
         (a "hello world"))
    (let ((private 'secret)) 
        (s-lex-format control-string))))
==> Lisp error: (error "Undefined variable private")



Or, you could just use explicitely the with-environment macro:

(let ((control-string "${a} - the answer is ${v}"))
   (let ((v 42)
         (a "hello world")
         (private 'secret))
     (with-environment (env v a)
        (s-lex-format* control-string env))))
--> "hello world - the answer is 42"


Also, notice that if the parameters are not known at compilation time,
there's little reason to use a macro…  You could as well have written:

(let ((control-string "${a} - the answer is ${v}"))
   (let ((v 42)
         (a "hello world")
         (private 'secret))
     (s-lex-format* control-string (list 'a a 'v v))))
--> "hello world - the answer is 42"




-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
A bad day in () is better than a good day in {}.
You can take the lisper out of the lisp job, but you can't take the lisp out
of the lisper (; -- antifuchs




^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-05 20:34 ` Dmitry Gutov
@ 2013-06-05 22:41   ` Stefan Monnier
  2013-06-05 23:46     ` Dmitry Gutov
  0 siblings, 1 reply; 9+ messages in thread
From: Stefan Monnier @ 2013-06-05 22:41 UTC (permalink / raw)
  To: Dmitry Gutov; +Cc: Nic Ferrier, emacs-devel

> Somewhat relatedly, I'd really like to see `debug' and `edebug' support
> local variable evaluation in lexical scoping environment.  Apparently,
> it's rather hard to implement.

The recent "merge specpdl and backtrace" is a step in this direction.
IOW, it's coming, tho not very fast.


        Stefan



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: macros and the lexical environment
  2013-06-05 22:41   ` Stefan Monnier
@ 2013-06-05 23:46     ` Dmitry Gutov
  0 siblings, 0 replies; 9+ messages in thread
From: Dmitry Gutov @ 2013-06-05 23:46 UTC (permalink / raw)
  To: Stefan Monnier; +Cc: Nic Ferrier, emacs-devel

Stefan Monnier <monnier@IRO.UMontreal.CA> writes:

>> Somewhat relatedly, I'd really like to see `debug' and `edebug' support
>> local variable evaluation in lexical scoping environment.  Apparently,
>> it's rather hard to implement.
>
> The recent "merge specpdl and backtrace" is a step in this direction.
> IOW, it's coming, tho not very fast.

That's a very good news.



^ permalink raw reply	[flat|nested] 9+ messages in thread

end of thread, other threads:[~2013-06-05 23:46 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz follow: Atom feed
-- links below jump to the message on this page --
2013-06-04 21:48 macros and the lexical environment Nic Ferrier
2013-06-04 23:07 ` Pascal J. Bourguignon
2013-06-05  8:23   ` Nic Ferrier
2013-06-05  8:35     ` Jambunathan K
2013-06-05 21:08     ` Pascal J. Bourguignon
2013-06-05  1:48 ` Stefan Monnier
2013-06-05 20:34 ` Dmitry Gutov
2013-06-05 22:41   ` Stefan Monnier
2013-06-05 23:46     ` Dmitry Gutov

Code repositories for project(s) associated with this public inbox

	https://git.savannah.gnu.org/cgit/emacs.git

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).