Lisp HUG Maillist Archive

Defensive Multithreaded Coding...

As a result of my recent bout of confusion regarding the priorities of Common Lisp binding mechanisms, I had to come up with something to protect the code from all future REPL hackings that might cause unintentional special bindings to occur. Of course this would only matter if you need to recompile a source after playing at the keyboard. But that situation happens almost all the time for me.

I really don’t want a protective mechanism that causes recompiles to fail. I’d much rather have a system that simply defends against future problems. So I came up with a set of macros for ensuring lexical bindings. However, they use symbol-macrolet to avoid the need for a code walker. So in any event, a compile with raise an error signal if any of the mentioned names are already bound at the global level.

Here is an example of use:

;; 1m10s to compare entire Lispworks trees between Dachshund and Malachite!!
(defun compare-system (path node node-path)
  (um:ensure-lexical (path node node-path)
    (um:llet (tree-a tree-b)
      (um:par
        (setf tree-a (grand-hash path))
        (setf tree-b (bfly:!? (concatenate 'string "eval@" node)
                              `(grand-hash ,node-path))))
      (compare-directory tree-a tree-b))))


This code will execute two filesystem hashing scans in parallel on two machines connected over a secure network channel. Each form inside the um:par clause may be fired off into another thread for execution. They rendezvous at the close of the um:par clause.

But references inside those worker forms are to free vars for PATH, NODE, NODE-PATH, TREE-A, and TREE-B. Hence, if any of these are names of global bindings, then the code would fail except for the use of ENSURE-LEXICAL and the LLET.

You normally don’t know and don’t care whether the names of function args happen to also name global bindings. They are bound on entry, and behave essentially the same inside the body of the function. But any embedded lambda closures that may be performed in another thread really will care if they refer to these function args. Unless you can be sure that the free vars refer to lexically bound vars that refer to the arguments, you will instead end up looking at blank globals belonging to the host thread that runs the lambda closure. Kaboom! ENSURE-LEXICAL and LLET give you some defensive tactics against such errors.

(defmacro llet (bindings &body body)
  ;; enforce lexical binding by way of alpha conversion
  ;; of the binding symbols
  ;;
  ;; symbol-macrolet will signal an error if one of the symbols
  ;; in the llet is named in a special declaration
  (multiple-value-bind (new-bindings new-body)
      (rebindings bindings body)
    `(let ,new-bindings
       ,new-body)))


(defmacro llet* (bindings &body body)
  `(llet (,(car bindings))
     ,@(if (cdr bindings)
           `((llet* ,(cdr bindings)
              ,@body))
         body)))

(defmacro ensure-lexical (syms &body body)
  ;; Use this to ensure that free vars inside body lambda closures
  ;; refer to lexically bound values.
  ;;
  ;; Note that because of the symbol-macrolet, if any symbols in the list
  ;; are already bound specially, compiling will signal an error.
  (let* ((gnames   (mapcar (um:compose #'gensym #'string) syms)))
    `(let ,(mapcar #'list gnames syms)
       (symbol-macrolet ,(mapcar #'list syms gnames)
         ,@body))))

(defun rebindings (bindings body)
  (let* ((names        (get-binding-syms bindings))
         (gnames       (mapcar (um:compose #'gensym #'string) names))
         (new-bindings (mapcar #'(lambda (binding gname)
                                   (if (consp binding)
                                       `(,gname ,@(cdr binding))
                                     gname))
                               bindings gnames)))
    (values new-bindings
            `(symbol-macrolet ,(mapcar #'list names gnames)
               ,@body))))

(defun get-binding-sym (binding)
  (if (consp binding)
      (car binding)
    binding))

(defun get-binding-syms (bindings)
  (mapcar #'get-binding-sym bindings))


- DM

Re: Defensive Multithreaded Coding...

Here’s an additional extension to help avoid mis-using the ENSURE-LEXICAL. It creates a closure, like lambda, but ensures that stated free-vars are bound over lexically at the time of closure creation.

(defmacro llambda ((args &key free-vars) &body body)
  ;; create a lambda closure with the free-vars bound lexically
  ;; to their extant values at the time of closure creation
  `(ensure-lexical ,free-vars
     #'(lambda ,args
         ,@body)))


Example:

(defun sexpEvt (&key flush (stream *standard-input*) read-eval)
  ;; an event that waits for a SEXP of input from the keyboard
  (execEvt (um:llambda (() :free-vars (flush stream read-eval))
             (when flush
               (flushInp stream))
             (let ((*read-eval* read-eval))
               (read stream)))
           ))

Here the args to the function sexpEvt are used as free-vars inside the lambda closure. So to be sure that we get the bound function argument values when the closure is executed, in whatever thread, we use LLAMBDA and state those free vars to be lexically bound over before the closure is constructed.

If there is the slightest doubt about what thread might perform a closure, it is best to use LLAMBDA.

Too bad there isn’t a way to automate the extraction of free vars inside of lambda expressions. You have to do this manually to provide the :free-vars list. And there might be some time when you really don’t want all the free vars bound over lexically. I can’t think of any times off hand, but it is possible. In that case just elide them from the :free-vars list.

But by placing the free vars next to the lambda closure expression, it becomes easier to see which free vars really need to be bound over lexically. Just using ENSURE-LEXICAL at the top of some function body might have you miss one or overstate the situation.

- DM

Re: Defensive Multithreaded Coding...

Here is a version that automatically scans the body of lambda closures and provides lexical bindings for global specials and rewrites the body to reference those lexical bindings. (Whew!)

The only cases we are ever concerned about are lambda closures passed to another thread for execution. Hence, there is just one macro, named MP-LAMBDA which is used exactly like LAMBDA. If the body has free vars that are globally bound at the time of compile, then a let-over-lambda is formed, otherwise just the lambda.

To cover those rare cases when you really do want to refer to a global, despite the fact that who-knows-what the binding value will be in some foreign thread, then the arg keywords list for MP-LAMBDA has been extended to allow &GLOBAL followed by one symbol or a list of symbols that should *not* receive local lexical bindings around the lambda closure.

Example:

(mp-lambda (a b c)
(declare (ignore c))
(+ x a b))

When x is not a global special, this just becomes a standard lambda closure with no additional pre-bindings. Presumably the surrounding context provides a lexical binding for x. But if x has been declared as global special, this is converted into 

(LET ((#:X57364 X)) #'(LAMBDA (A B C) (DECLARE (IGNORE C)) (+ #:X57364 A B)))

But if you really do want to refer to the global binding for x, then use this:

(mp-lambda (a b c &global x)
(declare (ignore c))
(+ x a b))

Then, since there are no remaining free vars referring to globals inside the body of the lambda, this will just become a standard lambda with no pre-bindings again. The &GLOBAL and its parameter are elided before passing along the args list to LAMBDA.

The intent is that if you form any lambda closures with an eye toward having them executed in another thread, then you should write MP-LAMBDA instead of LAMBDA.

Unlike SYMBOL-MACROLET, there are no errors resulting from attempted rewrites if there really are global specials already defined. Symbol-macrolet in this application is actually quite useless because it would do nothing if there were no global specials, (I wouldn’t have issued any symbol-macrolets in that case), and when there are some extant global bindings, then symbol-macrolet forces an error condition.

One caveat is that I stole the rewriting actions from LW’s WALKER. So this probably isn’t portable to any other Lisp. Furthermore, there results some nuisance warnings on things like the (declare (ignore c)) shown above, and some unused symbol-macrolets when using WITH-SLOTS. The code looks correct on walk through, so there must be some interaction with my walking an rewriting the code. It looks like macro expansion may have already occurred before I get my hands on the body code, but then I leave those declares and symbol-macrolets in place.

——————————————————————

(defun rewrite (names gnames body)
  (let ((alst (pairlis names gnames)))
    (labels ((rewriter (subform context env)
               (declare (ignore context))
               (let ((pair (and (symbolp subform)
                                ;; presumably, this avoids inner let rebindings...
                                (not (walker:variable-lexical-p subform env))
                                (assoc subform alst))))
                 (if pair
                     (cdr pair)
                   subform))))
      (walker:walk-form body nil #'rewriter))))

(defun find-global-free-vars (body)
  (let ((free-vars nil))
    (labels ((walk (subform context env)
               (declare (ignore context))
               (when (and (symbolp subform)
                          (not (walker:variable-lexical-p subform env))
                          (sys:declared-special-p subform))
                 (pushnew subform free-vars))
               subform))
      (walker:walk-form body nil #'walk)
      free-vars)))

(defun mklist (arg)
  (if (consp arg)
      arg
    (list arg)))

(defun remove-pair (lst pos)
  (if pos
      (append (subseq lst 0 pos)
              (subseq lst (min (+ 2 pos) (length lst))))
    lst))

(defmacro mp-lambda (args &body body)
  (let* ((kws-pos    (position '&global args))
         (exceptions (when kws-pos
                       (mklist (nth (1+ kws-pos) args))))
         (new-args   (remove-pair args kws-pos))
         (globals    (set-difference (find-global-free-vars body)
                                     exceptions)))
    (if globals
        (let* ((gnames  (mapcar (lambda (name)
                                  (gensym (string name)))
                                globals))
               (new-bindings  (mapcar #'list gnames globals))
               (new-body      (rewrite globals gnames body)))
          `(let ,new-bindings
             (lambda ,new-args
               ,@new-body)))
      ;; else
      `(lambda ,new-args
         ,@body))))


Re: Defensive Multithreaded Coding...

I considerably cleaned up and refactored the code. I also tracked down the source of the spurious warnings and modified my approach a bit. Instead of walking the lambda body, it was necessary to provide a proper context for declares and symbol-macrolets by constructing an entire lambda form for the walker to walk.

New code more efficiently handles the &global keywords in mp-lambda arglists, and permits as many of them as you like in a single arglist.

——————————————
(defun rewrite (body dict)
  (labels ((rewriter (subform context env)
             (declare (ignore context))
             (let ((pair (and (symbolp subform)
                              ;; presumably, this avoids inner let rebindings...
                              (not (walker:variable-lexical-p subform env))
                              (assoc subform dict))))
               (if pair
                   (cdr pair)
                 subform))))
    (walker:walk-form body nil #'rewriter)))

(defun find-global-free-vars (body)
  (let ((free-vars nil))
    (labels ((walk (subform context env)
               (declare (ignore context))
               (when (and (symbolp subform)
                          (not (walker:variable-lexical-p subform env))
                          (sys:declared-special-p subform))
                 (pushnew subform free-vars))
               subform))
      (walker:walk-form body nil #'walk)
      free-vars)))

(defun mklist (arg)
  (if (listp arg)
      arg
    (list arg)))

(defun is-&global (item)
  (and (symbolp item)
       (string-equal #.(string '&global) item)))

(defun process-args (args)
  (let (exceptions)
    (labels ((trim (lst)
               (unless (endp lst)
                 (cond ((is-&global (car lst))
                        (setf exceptions (append (mklist (cadr lst)) exceptions))
                        (trim (cddr lst)))

                       (t
                        (cons (car lst)
                              (trim (cdr lst))))
                       ))))
      (let ((new-args (trim args)))
        (values new-args exceptions))
      )))

(defun gensym-like (sym)
  (gensym (string sym)))

(defun rewrite-with-lexical-bindings (globals body)
  (let* ((gnames        (mapcar #'gensym-like globals))
         (new-bindings  (mapcar #'list gnames globals))
         (new-body      (rewrite body (pairlis globals gnames))))
    (values new-bindings new-body)))
  
(defmacro mp-lambda (args &body body)
  (multiple-value-bind (new-args exceptions)
      (process-args args)
    (let* ((tmp-body `(lambda ,new-args ,@body))
           (globals (set-difference (find-global-free-vars tmp-body)
                                    exceptions)))
      (if globals
          (multiple-value-bind (new-bindings new-body)
              (rewrite-with-lexical-bindings globals tmp-body)
            `(let ,new-bindings
               ,new-body))
        ;; else
        tmp-body) )))

(editor:setup-indent "mp-lambda" 1)



_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

There is one other case that I can think of, after reviewing my MP oriented codes… Many times a function will utilize local functions via FLET or LABELS. Those implicitly form functional closures when passed as first class objects to other functions or bound to some name. If there is the slightest chance of these being executed in another thread, then they also need to become made safe.

So I invent another macro (ENSURE-LEXICAL-BINDINGS args &body body) which scans and rewrites (if needed) the body to make use of new lexical bindings to cover any extant dynamic binding references in the body. The args is usually NIL, but can take one keyword :GLOBAL which should furnish a symbol or a list of symbols that should be treated as dynamically bound anyway. The use of the :GLOBAL argument will prevent making new lexical bindings for those symbols.

Example:

(defun diddly ()
	(ensure-lexical-bindings (:global base)
		(flet ((my-local-fn (x)
				…))
			(mp:funcall-async #’my-local arg)))

Because you can’t know, in general, whether a symbol has been previously bound dynamically by the time you compile a new function, and the fact that there is no syntactic distinction between dynamic and lexical binding, the use of ENSURE-LEXICAL-BINDINGS is necessary for avoiding unpleasant surprises when your FLET and LABELS functions are, or could be, fired off into another thread.

Original Lisp didn’t have multiprocessing, and so it couldn’t foresee the possibilities arising from design choices. I appreciate that the path chosen by LW and many others is expedient, and runtime efficient. And so we must become more aware in our code of potential pitfalls as a result. 

I must say, the LW folks did “told you so…”, but only in the vaguest manner, by stating that each thread has its own dynamic binding environment. What, exactly, were the implications? We now see… How much old code would really break if LAMBDA, FLET, and LABELS were redesigned to produce lexical bindings by default?

————————————————
;; Augments MP-LABEL code…

(defmacro ensure-lexical-bindings ((&key global) &body body)
  (let ((globals (set-difference (find-global-free-vars body)
                                 (mklist global))))
    (if globals
        (multiple-value-bind (new-bindings new-body)
            (rewrite-with-lexical-bindings globals body)
          `(let ,new-bindings
             ,@new-body))
      ;; else
      `(progn
         ,@body))
    ))

(editor:setup-indent "ensure-lexical-bindings" 1)


> On Oct 10, 2017, at 04:03, David McClain <dbm@refined-audiometrics.com> wrote:
> 
> I considerably cleaned up and refactored the code. I also tracked down the source of the spurious warnings and modified my approach a bit. Instead of walking the lambda body, it was necessary to provide a proper context for declares and symbol-macrolets by constructing an entire lambda form for the walker to walk.
> 
> New code more efficiently handles the &global keywords in mp-lambda arglists, and permits as many of them as you like in a single arglist.
> 
> ——————————————
> (defun rewrite (body dict)
>  (labels ((rewriter (subform context env)
>             (declare (ignore context))
>             (let ((pair (and (symbolp subform)
>                              ;; presumably, this avoids inner let rebindings...
>                              (not (walker:variable-lexical-p subform env))
>                              (assoc subform dict))))
>               (if pair
>                   (cdr pair)
>                 subform))))
>    (walker:walk-form body nil #'rewriter)))
> 
> (defun find-global-free-vars (body)
>  (let ((free-vars nil))
>    (labels ((walk (subform context env)
>               (declare (ignore context))
>               (when (and (symbolp subform)
>                          (not (walker:variable-lexical-p subform env))
>                          (sys:declared-special-p subform))
>                 (pushnew subform free-vars))
>               subform))
>      (walker:walk-form body nil #'walk)
>      free-vars)))
> 
> (defun mklist (arg)
>  (if (listp arg)
>      arg
>    (list arg)))
> 
> (defun is-&global (item)
>  (and (symbolp item)
>       (string-equal #.(string '&global) item)))
> 
> (defun process-args (args)
>  (let (exceptions)
>    (labels ((trim (lst)
>               (unless (endp lst)
>                 (cond ((is-&global (car lst))
>                        (setf exceptions (append (mklist (cadr lst)) exceptions))
>                        (trim (cddr lst)))
> 
>                       (t
>                        (cons (car lst)
>                              (trim (cdr lst))))
>                       ))))
>      (let ((new-args (trim args)))
>        (values new-args exceptions))
>      )))
> 
> (defun gensym-like (sym)
>  (gensym (string sym)))
> 
> (defun rewrite-with-lexical-bindings (globals body)
>  (let* ((gnames        (mapcar #'gensym-like globals))
>         (new-bindings  (mapcar #'list gnames globals))
>         (new-body      (rewrite body (pairlis globals gnames))))
>    (values new-bindings new-body)))
> 
> (defmacro mp-lambda (args &body body)
>  (multiple-value-bind (new-args exceptions)
>      (process-args args)
>    (let* ((tmp-body `(lambda ,new-args ,@body))
>           (globals (set-difference (find-global-free-vars tmp-body)
>                                    exceptions)))
>      (if globals
>          (multiple-value-bind (new-bindings new-body)
>              (rewrite-with-lexical-bindings globals tmp-body)
>            `(let ,new-bindings
>               ,new-body))
>        ;; else
>        tmp-body) )))
> 
> (editor:setup-indent "mp-lambda" 1)
> 
> 
> 
> _______________________________________________
> Lisp Hug - the mailing list for LispWorks users
> lisp-hug@lispworks.com
> http://www.lispworks.com/support/lisp-hug.html
> 


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

… there is nothing wrong with referring to a declared constant from any arbitrary thread… These happen also to be declared as special bindings, but they can never be accidentally rebound or altered. So fix the code to forego lexical rebinding of declared constants. 

And while we’re at it, improve efficiency by performing a one-pass scan / rewrite, and fix the problem of leftover symbol-macrolets, which cause spurious warnings during compile.

;; -----------------------------------------------------------------
;; ENSURE-LEXICAL-BINDINGS & MP-LAMBDA macros and their walking
;; scanner/rewriter

(defun rebind-global-free-vars (form global-exceptions)
  ;; Single-pass scan and rewrite, looking for symbols that have
  ;; global special bindings. We build up a dictionary as an alist and
  ;; hand it back to the caller so he can generate lexical bindings
  ;; around our newly macro-expanded and rewritten form.
  ;;
  ;; global-exceptions is a list of symbols that should be excluded
  ;; from rewriting.
  ;;
  (let (free-vars)
    (labels ((get-replacement (sym)
               (or (sys:cdr-assoc sym free-vars)
                   (let ((gname (gensym (string sym))))
                     (setf free-vars (acons sym gname free-vars))
                     gname)))

             (convert-pair-to-revlist (pair)
               (destructuring-bind (sym . gsym) pair
                 (list gsym sym)))

             (get-bindings-form ()
               (mapcar #'convert-pair-to-revlist free-vars))
             
             (rewrite (subform context env)
               (declare (ignore context))
               (cond ((and (symbolp subform)
                           (not (constantp subform))
                           (not (walker:variable-lexical-p subform env))
                           (sys:declared-special-p subform))
                      
                      (if (member subform global-exceptions)
                          subform
                        (get-replacement subform)))
                     

                     ;; This shouldn't be our problem... but when the
                     ;; walker encounters a symbol-macrolet form, it
                     ;; macroexpands all the symbols, but leaves the
                     ;; symbol-macrolet and its bindings in place. A
                     ;; subsequent repeat walk through from the
                     ;; compiler will trigger a warning that none of
                     ;; the symbol-macrolet bindings were referenced.
                     ;;
                     ;; So, we take the liberty of liberating the
                     ;; walked form of the symbol-macrolet and its
                     ;; bindings and plant the rest of the clauses
                     ;; into a progn. That keeps the system quiet.
                     ;;
                     ((and (consp subform)
                           (eql 'symbol-macrolet (car subform)))
                      `(progn ,@(cddr (walker:walk-form subform))))
                     
                     (t
                      subform)
                     )))
      (let ((expansion (walker:walk-form form nil #'rewrite)))
        (if free-vars
            `(let ,(get-bindings-form)
               ,expansion)
          ;; else
          expansion)) )))

(defun mklist (arg)
  (if (listp arg)
      arg
    (list arg)))

(defvar *in-scan* nil) ;; prevents all but outermost scan from occurring

(defmacro ensure-lexical-bindings ((&key global) form)
  ;; keyword arg global is really a symbol or a list of symbols that
  ;; should be excluded from lexical rebinding, remaining special
  ;; bindings in the form. (so-called global-exceptions). These should
  ;; be rare, so the default case is to assume that globals require
  ;; lexical rebindings around the form.
  (if *in-scan*
      form
    ;; else
    (let ((*in-scan* t))
      (rebind-global-free-vars form (mklist global))) ))

;; ------------------------------------------------------------

(defun process-args (args)
  (let (global-exceptions)
    (labels ((is-&global (item)
               (and (symbolp item)
                    (string-equal #.(string '&global) item)))
               
             (trim (lst)
               (unless (endp lst)
                 (cond ((is-&global (car lst))
                        (setf global-exceptions (append (mklist (cadr lst)) global-exceptions))
                        (trim (cddr lst)))

                       (t
                        (cons (car lst)
                              (trim (cdr lst))))
                       ))))
      (let ((new-args (trim args)))
        (values new-args global-exceptions))
      )))

(defmacro mp-lambda (args &body body)
  (multiple-value-bind (new-args global-exceptions)
      (process-args args)
    `(ensure-lexical-bindings (:global ,global-exceptions)
       (lambda ,new-args ,@body))))

(editor:setup-indent "mp-lambda" 1)
(editor:setup-indent "ensure-lexical-bindings" 1)


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

Wow! I just ran into a really subtle issue on this stuff…

The macros work just fine, but their placement position in the client code can make a huge difference. And it appears that attempting to patch things up in the walker is not possible.

Example:

(defun compare-system (path node node-path)
  (let (tree-a tree-b)
    (um:ensure-lexical-bindings ()  ;; <— this is the proper location
      (um:par
        (setf tree-a (grand-hash path))
        (setf tree-b (bfly:!? (concatenate 'string "eval@" node)
                              `(grand-hash ,node-path))))
      (compare-directory tree-a tree-b))))


Version 2:

(defun compare-system (path node node-path)
  (um:ensure-lexical-bindings () ;; <— this is an improper location
    (let (tree-a tree-b)
      (um:par
        (setf tree-a (grand-hash path))
        (setf tree-b (bfly:!? (concatenate 'string "eval@" node)
                              `(grand-hash ,node-path))))
      (compare-directory tree-a tree-b))))

In the second version, the macro works just fine by alpha converting all references to special globals, and capturing their bound values at the location of the macro. But then we come along and possibly modify one or more of them in the following LET form. If either of tree-a or tree-b were accidentally declared as special globals, our captured binding values will be old news, and the clients of those captured values might not like it.

The first version is correctly positioned because it comes after any possible rebindings of special globals and captures their updated binding values before alpha conversion.

In order to have this situation corrected automatically, the walker would have to spot the location of LET bindings after the ensure-lexical-bindings macro, and then insert some more bindings for capturing updated values. But once you issue a rewrite inside of the walker, it scans your rewritten code again, and we would end up in an endless loop.

So this appears to require careful thinking by the programmer, and manual placement of ensure-lexical-bindings must be carefully crafted.

It would almost be safe to just use mp-lambda forms, which arranges capture bindings just around the alpha converted lambda form. But then it would become difficult to share information between threads, as in this example where thread results are planted in tree-a and tree-b for later consideration after the (PAR …) form. So that doesn’t work either.

- DM

Re: Defensive Multithreaded Coding...

Ahah! I can fully automate it using 3 separate walkthrough passes. 

First walkthrough expands all the macros, just in case someone has a special version of LET or LET* for themselves (called My-Let or some such thing). This scan also performs symbol macrolet substitutions.

Second walkthrough performs full alpha conversion on referenced global symbols, and marks the location of LET and LET* re-bindings with such globals using a unique marker symbol inserted in front of the LET. This scan also removes the gratuitous symbol-macrolet’s that were left in the rewrite from the first pass, to eliminate spurious warning messages during compile.

Third and final walkthrough looks for those markers and rewrites the LET clauses to insert a nested LET with lexical capture of the newly re-bound globals that precede, along with the body of the original LET clause.

Result is fully automated and trustworthy lexical rewrites of your code. Now I’ll look for ways to improve efficiency. I can probably merge passes 1 and 2 already.

- DM


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier. 

Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.

The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.

But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.

Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).

The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.

The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.

Cheers,

- DM

_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

RE: Defensive Multithreaded Coding...

Hi Chun,

I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.

However, one question remains: why is the code walker's current source not available for viewing?

Thanks,

Toomas

-----Original Message-----
From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
Sent: 12. lokakuuta 2017 12:58
To: David McClain <dbm@refined-audiometrics.com>
Cc: Harlequin User Group <lisp-hug@lispworks.com>
Subject: Re: Defensive Multithreaded Coding...

Good job $B!D(B

P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won$B!G(Bt send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.

> $B:_(B 12 ott 2017$B!$(B11:21$B!$(BDavid McClain <dbm@refined-audiometrics.com> $B<LF;!'(B
> 
> Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.
> 
> Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.
> 
> The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.
> 
> But$B!D(B the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.
> 
> Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).
> 
> The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.
> 
> The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.
> 
> Cheers,
> 
> - DM
> 
> _______________________________________________
> Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com 
> http://www.lispworks.com/support/lisp-hug.html


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

BTW… this should be pointed out… The current definition of a global special in the walker callback is:

         (is-global (sym env)
           (and (symbolp sym)
            ;;
            ;; DEFCONSTANT produces a special binding,
            ;; but it can't be accidentally rebound or
            ;; redefined, so it is okay for other
            ;; threads to use this truly global fixed
            ;; values
            ;;
            (not (constantp sym))
            ;;
            ;; once declared special with DEFVAR or DEFPARAMETER you
            ;; can never bind a symbol lexically. The only way to
            ;; remove its special property is to unintern it.
            ;;
            (or (sys:declared-special-p sym)
                ;;
                ;; and using (DECLARE SPECIAL) can make
                ;; dynamic bindings, even if there is
                ;; no global declaration with that
                ;; symbol. But these local special
                ;; bindings can be overridden by an
                ;; inner lexical binding with the same
                ;; symbol.
                ;;
                (walker:variable-special-p sym env))
            ;;
            ;; make sure we aren't supposed to ignore this symbol
            ;;
            (not (member sym global-exceptions))))

        The red highlighted line shows the main distinction from earlier versions. The Walker keeps track of a lot of information in the variables environment when it sees LET bindings. When external globals have already been declared somewhere else, the Walker probably isn’t aware of them, and that’s the reason for my SYS:DECLARED-SPECIAL-P. But the Walker does understand lexical and locally declared special bindings. And while you can never override a globally declared special binding (except by UNINTERN), the use of (DECLARE SPECIAL) *can* be overridden by an enclosed LET, and the Walker seems to understand that.

So the prior sources showed something like (NOT (WALKER:VARIABLE-LEXICAL-P)) that isn’t the correct test. It should be (WALKER:VARIABLE-SPECIAL-P) as shown above.

… at least, I think so now…

(Finish what? … how does one know when it is finished, whatever *it* is? These ramblings produce an archive on Google for someday when someone else runs into the same problems and wants to search for prior resolutions.)

- DM



On Oct 12, 2017, at 05:16, Toomas Altosaar <toomas.altosaar@fi.abb.com> wrote:

Hi Chun,

I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.

However, one question remains: why is the code walker's current source not available for viewing?

Thanks,

Toomas

-----Original Message-----
From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
Sent: 12. lokakuuta 2017 12:58
To: David McClain <dbm@refined-audiometrics.com>
Cc: Harlequin User Group <lisp-hug@lispworks.com>
Subject: Re: Defensive Multithreaded Coding...

Good job …

P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won’t send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.

在 12 ott 2017,11:21,David McClain <dbm@refined-audiometrics.com> 写道:

Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.

Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.

The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.

But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.

Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).

The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.

The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.

Cheers,

- DM

_______________________________________________
Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html


Re: Defensive Multithreaded Coding...

I think what you actually need is

(eq (hcl:variable-information sym env) :special)

which deals with global and local declarations.

-- 
Martin Simmons
LispWorks Ltd
http://www.lispworks.com/


>>>>> On Thu, 12 Oct 2017 05:41:09 -0700, David McClain said:
> 
> BTW… this should be pointed out… The current definition of a global special in the walker callback is:
> 
>          (is-global (sym env)
>            (and (symbolp sym)
>             ;;
>             ;; DEFCONSTANT produces a special binding,
>             ;; but it can't be accidentally rebound or
>             ;; redefined, so it is okay for other
>             ;; threads to use this truly global fixed
>             ;; values
>             ;;
>             (not (constantp sym))
>             ;;
>             ;; once declared special with DEFVAR or DEFPARAMETER you
>             ;; can never bind a symbol lexically. The only way to
>             ;; remove its special property is to unintern it.
>             ;;
>             (or (sys:declared-special-p sym)
>                 ;;
>                 ;; and using (DECLARE SPECIAL) can make
>                 ;; dynamic bindings, even if there is
>                 ;; no global declaration with that
>                 ;; symbol. But these local special
>                 ;; bindings can be overridden by an
>                 ;; inner lexical binding with the same
>                 ;; symbol.
>                 ;;
>                 (walker:variable-special-p sym env))
>             ;;
>             ;; make sure we aren't supposed to ignore this symbol
>             ;;
>             (not (member sym global-exceptions))))
> 
>         The red highlighted line shows the main distinction from earlier versions. The Walker keeps track of a lot of information in the variables environment when it sees LET bindings. When external globals have already been declared somewhere else, the Walker probably isn’t aware of them, and that’s the reason for my SYS:DECLARED-SPECIAL-P. But the Walker does understand lexical and locally declared special bindings. And while you can never override a globally declared special binding (except by UNINTERN), the use of (DECLARE SPECIAL) *can* be overridden by an enclosed LET, and the Walker seems to understand that.
> 
> So the prior sources showed something like (NOT (WALKER:VARIABLE-LEXICAL-P)) that isn’t the correct test. It should be (WALKER:VARIABLE-SPECIAL-P) as shown above.
> 
> … at least, I think so now…
> 
> (Finish what? … how does one know when it is finished, whatever *it* is? These ramblings produce an archive on Google for someday when someone else runs into the same problems and wants to search for prior resolutions.)
> 
> - DM
> 
> 
> 
> > On Oct 12, 2017, at 05:16, Toomas Altosaar <toomas.altosaar@fi.abb.com> wrote:
> > 
> > Hi Chun,
> > 
> > I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.
> > 
> > However, one question remains: why is the code walker's current source not available for viewing?
> > 
> > Thanks,
> > 
> > Toomas
> > 
> > -----Original Message-----
> > From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
> > Sent: 12. lokakuuta 2017 12:58
> > To: David McClain <dbm@refined-audiometrics.com>
> > Cc: Harlequin User Group <lisp-hug@lispworks.com>
> > Subject: Re: Defensive Multithreaded Coding...
> > 
> > Good job …
> > 
> > P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won’t send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.
> > 
> >> 在 12 ott 2017,11:21,David McClain <dbm@refined-audiometrics.com> 写道:
> >> 
> >> Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.
> >> 
> >> Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.
> >> 
> >> The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.
> >> 
> >> But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.
> >> 
> >> Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).
> >> 
> >> The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.
> >> 
> >> The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.
> >> 
> >> Cheers,
> >> 
> >> - DM
> >> 
> >> _______________________________________________
> >> Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com 
> >> http://www.lispworks.com/support/lisp-hug.html
> > 
> > 
> > _______________________________________________
> > Lisp Hug - the mailing list for LispWorks users
> > lisp-hug@lispworks.com
> > http://www.lispworks.com/support/lisp-hug.html
> > 

_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

Thanks Martin,

But when I substitute your recommended test in place of my OR clause with SYS:DECLARED-SPECIAL-P and WALKER:VARIABLE-SPECIAL-P, then my alpha conversion stops working.

Here is my test example:

(defvar x 15)  ;; <— plant a global special

;; then walk this
(let ((u 1)
      (x 32)
      (y 15))
  (declare (special y))
  (locally ;; let ((y 77))  ;; <— allows me to test for a lexical override on special
    (ensure-lexical-bindings ()
      (let ((v 2)
            (x "twently"))
        (ensure-lexical-bindings ()
          (symbol-macrolet ((c 3))
            (mp-lambda (x a b)
              (+ x y a b c))))))))


With your recommended HCL:VARIABLE-INFORMATION I get the following as a Walker result:

(LET ((U 1) (X 32) (Y 15)) (DECLARE (SPECIAL Y)) (LOCALLY (LET ((V 2) (X "twently")) #'(LAMBDA (X A B) (+ X Y A B 3)))))

But with my original code I get this:

(LET ((U 1) (X 32) (Y 15))
  (DECLARE (SPECIAL Y))
  (LOCALLY
    (LET ((#:Y50649 Y) (#:X50648 X))
      (DECLARE (IGNORABLE #:Y50649 #:X50648))
      (LET ((V 2) (X "twently")) (LET ((#:X50648 X)) (DECLARE (IGNORABLE #:X50648)) #'(LAMBDA (#:X50648 A B) (+ #:X50648 #:Y50649 A B 3)))))))


- DM


> On Oct 12, 2017, at 07:10, Martin Simmons <martin@lispworks.com> wrote:
> 
> I think what you actually need is
> 
> (eq (hcl:variable-information sym env) :special)
> 
> which deals with global and local declarations.
> 
> -- 
> Martin Simmons
> LispWorks Ltd
> http://www.lispworks.com/
> 
> 
>>>>>> On Thu, 12 Oct 2017 05:41:09 -0700, David McClain said:
>> 
>> BTW… this should be pointed out… The current definition of a global special in the walker callback is:
>> 
>>         (is-global (sym env)
>>           (and (symbolp sym)
>>            ;;
>>            ;; DEFCONSTANT produces a special binding,
>>            ;; but it can't be accidentally rebound or
>>            ;; redefined, so it is okay for other
>>            ;; threads to use this truly global fixed
>>            ;; values
>>            ;;
>>            (not (constantp sym))
>>            ;;
>>            ;; once declared special with DEFVAR or DEFPARAMETER you
>>            ;; can never bind a symbol lexically. The only way to
>>            ;; remove its special property is to unintern it.
>>            ;;
>>            (or (sys:declared-special-p sym)
>>                ;;
>>                ;; and using (DECLARE SPECIAL) can make
>>                ;; dynamic bindings, even if there is
>>                ;; no global declaration with that
>>                ;; symbol. But these local special
>>                ;; bindings can be overridden by an
>>                ;; inner lexical binding with the same
>>                ;; symbol.
>>                ;;
>>                (walker:variable-special-p sym env))
>>            ;;
>>            ;; make sure we aren't supposed to ignore this symbol
>>            ;;
>>            (not (member sym global-exceptions))))
>> 
>>        The red highlighted line shows the main distinction from earlier versions. The Walker keeps track of a lot of information in the variables environment when it sees LET bindings. When external globals have already been declared somewhere else, the Walker probably isn’t aware of them, and that’s the reason for my SYS:DECLARED-SPECIAL-P. But the Walker does understand lexical and locally declared special bindings. And while you can never override a globally declared special binding (except by UNINTERN), the use of (DECLARE SPECIAL) *can* be overridden by an enclosed LET, and the Walker seems to understand that.
>> 
>> So the prior sources showed something like (NOT (WALKER:VARIABLE-LEXICAL-P)) that isn’t the correct test. It should be (WALKER:VARIABLE-SPECIAL-P) as shown above.
>> 
>> … at least, I think so now…
>> 
>> (Finish what? … how does one know when it is finished, whatever *it* is? These ramblings produce an archive on Google for someday when someone else runs into the same problems and wants to search for prior resolutions.)
>> 
>> - DM
>> 
>> 
>> 
>>> On Oct 12, 2017, at 05:16, Toomas Altosaar <toomas.altosaar@fi.abb.com> wrote:
>>> 
>>> Hi Chun,
>>> 
>>> I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.
>>> 
>>> However, one question remains: why is the code walker's current source not available for viewing?
>>> 
>>> Thanks,
>>> 
>>> Toomas
>>> 
>>> -----Original Message-----
>>> From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
>>> Sent: 12. lokakuuta 2017 12:58
>>> To: David McClain <dbm@refined-audiometrics.com>
>>> Cc: Harlequin User Group <lisp-hug@lispworks.com>
>>> Subject: Re: Defensive Multithreaded Coding...
>>> 
>>> Good job …
>>> 
>>> P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won’t send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.
>>> 
>>>> 在 12 ott 2017,11:21,David McClain <dbm@refined-audiometrics.com> 写道:
>>>> 
>>>> Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.
>>>> 
>>>> Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.
>>>> 
>>>> The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.
>>>> 
>>>> But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.
>>>> 
>>>> Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).
>>>> 
>>>> The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.
>>>> 
>>>> The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.
>>>> 
>>>> Cheers,
>>>> 
>>>> - DM
>>>> 
>>>> _______________________________________________
>>>> Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com 
>>>> http://www.lispworks.com/support/lisp-hug.html
>>> 
>>> 
>>> _______________________________________________
>>> Lisp Hug - the mailing list for LispWorks users
>>> lisp-hug@lispworks.com
>>> http://www.lispworks.com/support/lisp-hug.html
>>> 
> 
> _______________________________________________
> Lisp Hug - the mailing list for LispWorks users
> lisp-hug@lispworks.com
> http://www.lispworks.com/support/lisp-hug.html
> 


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

BTW, the nested ENSURE-LEXICAL-BINDINGS is redundant, as it should be. Only the outermost ensure does anything. Inner ones simply return their associated &body in walkthrough. So the second one in my test code was planted to be certain that nesting behavior is correct. Same goes for any MP-LAMBDA inside the scope of the ensure.

- DM

On Oct 12, 2017, at 08:19, David McClain <dbm@refined-audiometrics.com> wrote:

Thanks Martin,

But when I substitute your recommended test in place of my OR clause with SYS:DECLARED-SPECIAL-P and WALKER:VARIABLE-SPECIAL-P, then my alpha conversion stops working.

Here is my test example:

(defvar x 15)  ;; <— plant a global special

;; then walk this
(let ((u 1)
     (x 32)
     (y 15))
 (declare (special y))
 (locally ;; let ((y 77))  ;; <— allows me to test for a lexical override on special
   (ensure-lexical-bindings ()
     (let ((v 2)
           (x "twently"))
       (ensure-lexical-bindings ()
         (symbol-macrolet ((c 3))
           (mp-lambda (x a b)
             (+ x y a b c))))))))


With your recommended HCL:VARIABLE-INFORMATION I get the following as a Walker result:

(LET ((U 1) (X 32) (Y 15)) (DECLARE (SPECIAL Y)) (LOCALLY (LET ((V 2) (X "twently")) #'(LAMBDA (X A B) (+ X Y A B 3)))))

But with my original code I get this:

(LET ((U 1) (X 32) (Y 15))
 (DECLARE (SPECIAL Y))
 (LOCALLY
   (LET ((#:Y50649 Y) (#:X50648 X))
     (DECLARE (IGNORABLE #:Y50649 #:X50648))
     (LET ((V 2) (X "twently")) (LET ((#:X50648 X)) (DECLARE (IGNORABLE #:X50648)) #'(LAMBDA (#:X50648 A B) (+ #:X50648 #:Y50649 A B 3)))))))


- DM


On Oct 12, 2017, at 07:10, Martin Simmons <martin@lispworks.com> wrote:

I think what you actually need is

(eq (hcl:variable-information sym env) :special)

which deals with global and local declarations.

--
Martin Simmons
LispWorks Ltd
http://www.lispworks.com/


On Thu, 12 Oct 2017 05:41:09 -0700, David McClain said:

BTW… this should be pointed out… The current definition of a global special in the walker callback is:

       (is-global (sym env)
         (and (symbolp sym)
          ;;
          ;; DEFCONSTANT produces a special binding,
          ;; but it can't be accidentally rebound or
          ;; redefined, so it is okay for other
          ;; threads to use this truly global fixed
          ;; values
          ;;
          (not (constantp sym))
          ;;
          ;; once declared special with DEFVAR or DEFPARAMETER you
          ;; can never bind a symbol lexically. The only way to
          ;; remove its special property is to unintern it.
          ;;
          (or (sys:declared-special-p sym)
              ;;
              ;; and using (DECLARE SPECIAL) can make
              ;; dynamic bindings, even if there is
              ;; no global declaration with that
              ;; symbol. But these local special
              ;; bindings can be overridden by an
              ;; inner lexical binding with the same
              ;; symbol.
              ;;
              (walker:variable-special-p sym env))
          ;;
          ;; make sure we aren't supposed to ignore this symbol
          ;;
          (not (member sym global-exceptions))))

      The red highlighted line shows the main distinction from earlier versions. The Walker keeps track of a lot of information in the variables environment when it sees LET bindings. When external globals have already been declared somewhere else, the Walker probably isn’t aware of them, and that’s the reason for my SYS:DECLARED-SPECIAL-P. But the Walker does understand lexical and locally declared special bindings. And while you can never override a globally declared special binding (except by UNINTERN), the use of (DECLARE SPECIAL) *can* be overridden by an enclosed LET, and the Walker seems to understand that.

So the prior sources showed something like (NOT (WALKER:VARIABLE-LEXICAL-P)) that isn’t the correct test. It should be (WALKER:VARIABLE-SPECIAL-P) as shown above.

… at least, I think so now…

(Finish what? … how does one know when it is finished, whatever *it* is? These ramblings produce an archive on Google for someday when someone else runs into the same problems and wants to search for prior resolutions.)

- DM



On Oct 12, 2017, at 05:16, Toomas Altosaar <toomas.altosaar@fi.abb.com> wrote:

Hi Chun,

I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.

However, one question remains: why is the code walker's current source not available for viewing?

Thanks,

Toomas

-----Original Message-----
From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
Sent: 12. lokakuuta 2017 12:58
To: David McClain <dbm@refined-audiometrics.com>
Cc: Harlequin User Group <lisp-hug@lispworks.com>
Subject: Re: Defensive Multithreaded Coding...

Good job …

P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won’t send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.

在 12 ott 2017,11:21,David McClain <dbm@refined-audiometrics.com> 写道:

Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.

Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.

The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.

But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.

Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).

The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.

The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.

Cheers,

- DM

_______________________________________________
Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html


_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html



_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html


Re: Defensive Multithreaded Coding...

Sorry, forget that, it looks like the walker doesn't create the necessary
environment data for HCL:VARIABLE-INFORMATION to find specials.

-- 
Martin Simmons
LispWorks Ltd
http://www.lispworks.com/



>>>>> On Thu, 12 Oct 2017 08:19:43 -0700, David McClain said:
> 
> Thanks Martin,
> 
> But when I substitute your recommended test in place of my OR clause with SYS:DECLARED-SPECIAL-P and WALKER:VARIABLE-SPECIAL-P, then my alpha conversion stops working.
> 
> Here is my test example:
> 
> (defvar x 15)  ;; <— plant a global special
> 
> ;; then walk this
> (let ((u 1)
>       (x 32)
>       (y 15))
>   (declare (special y))
>   (locally ;; let ((y 77))  ;; <— allows me to test for a lexical override on special
>     (ensure-lexical-bindings ()
>       (let ((v 2)
>             (x "twently"))
>         (ensure-lexical-bindings ()
>           (symbol-macrolet ((c 3))
>             (mp-lambda (x a b)
>               (+ x y a b c))))))))
> 
> 
> With your recommended HCL:VARIABLE-INFORMATION I get the following as a Walker result:
> 
> (LET ((U 1) (X 32) (Y 15)) (DECLARE (SPECIAL Y)) (LOCALLY (LET ((V 2) (X "twently")) #'(LAMBDA (X A B) (+ X Y A B 3)))))
> 
> But with my original code I get this:
> 
> (LET ((U 1) (X 32) (Y 15))
>   (DECLARE (SPECIAL Y))
>   (LOCALLY
>     (LET ((#:Y50649 Y) (#:X50648 X))
>       (DECLARE (IGNORABLE #:Y50649 #:X50648))
>       (LET ((V 2) (X "twently")) (LET ((#:X50648 X)) (DECLARE (IGNORABLE #:X50648)) #'(LAMBDA (#:X50648 A B) (+ #:X50648 #:Y50649 A B 3)))))))
> 
> 
> - DM
> 
> 
> > On Oct 12, 2017, at 07:10, Martin Simmons <martin@lispworks.com> wrote:
> > 
> > I think what you actually need is
> > 
> > (eq (hcl:variable-information sym env) :special)
> > 
> > which deals with global and local declarations.
> > 
> > -- 
> > Martin Simmons
> > LispWorks Ltd
> > http://www.lispworks.com/
> > 
> > 
> >>>>>> On Thu, 12 Oct 2017 05:41:09 -0700, David McClain said:
> >> 
> >> BTW… this should be pointed out… The current definition of a global special in the walker callback is:
> >> 
> >>         (is-global (sym env)
> >>           (and (symbolp sym)
> >>            ;;
> >>            ;; DEFCONSTANT produces a special binding,
> >>            ;; but it can't be accidentally rebound or
> >>            ;; redefined, so it is okay for other
> >>            ;; threads to use this truly global fixed
> >>            ;; values
> >>            ;;
> >>            (not (constantp sym))
> >>            ;;
> >>            ;; once declared special with DEFVAR or DEFPARAMETER you
> >>            ;; can never bind a symbol lexically. The only way to
> >>            ;; remove its special property is to unintern it.
> >>            ;;
> >>            (or (sys:declared-special-p sym)
> >>                ;;
> >>                ;; and using (DECLARE SPECIAL) can make
> >>                ;; dynamic bindings, even if there is
> >>                ;; no global declaration with that
> >>                ;; symbol. But these local special
> >>                ;; bindings can be overridden by an
> >>                ;; inner lexical binding with the same
> >>                ;; symbol.
> >>                ;;
> >>                (walker:variable-special-p sym env))
> >>            ;;
> >>            ;; make sure we aren't supposed to ignore this symbol
> >>            ;;
> >>            (not (member sym global-exceptions))))
> >> 
> >>        The red highlighted line shows the main distinction from earlier versions. The Walker keeps track of a lot of information in the variables environment when it sees LET bindings. When external globals have already been declared somewhere else, the Walker probably isn’t aware of them, and that’s the reason for my SYS:DECLARED-SPECIAL-P. But the Walker does understand lexical and locally declared special bindings. And while you can never override a globally declared special binding (except by UNINTERN), the use of (DECLARE SPECIAL) *can* be overridden by an enclosed LET, and the Walker seems to understand that.
> >> 
> >> So the prior sources showed something like (NOT (WALKER:VARIABLE-LEXICAL-P)) that isn’t the correct test. It should be (WALKER:VARIABLE-SPECIAL-P) as shown above.
> >> 
> >> … at least, I think so now…
> >> 
> >> (Finish what? … how does one know when it is finished, whatever *it* is? These ramblings produce an archive on Google for someday when someone else runs into the same problems and wants to search for prior resolutions.)
> >> 
> >> - DM
> >> 
> >> 
> >> 
> >>> On Oct 12, 2017, at 05:16, Toomas Altosaar <toomas.altosaar@fi.abb.com> wrote:
> >>> 
> >>> Hi Chun,
> >>> 
> >>> I can see your point but since this topic can certainly be seen as being complex and not entirely derivable from Lisp specifications (due to threading issues that did not exist when the spec was written), I certainly have benefited in seeing the conditions, problem, and evolution of the solution through the e-mails covering this subject. If it would have just come out as one report in a "problem and solution pair" then I would have not probably spent time even reflecting on the issue. I learned something important.
> >>> 
> >>> However, one question remains: why is the code walker's current source not available for viewing?
> >>> 
> >>> Thanks,
> >>> 
> >>> Toomas
> >>> 
> >>> -----Original Message-----
> >>> From: owner-lisp-hug@lispworks.com [mailto:owner-lisp-hug@lispworks.com] On Behalf Of Chun Tian
> >>> Sent: 12. lokakuuta 2017 12:58
> >>> To: David McClain <dbm@refined-audiometrics.com>
> >>> Cc: Harlequin User Group <lisp-hug@lispworks.com>
> >>> Subject: Re: Defensive Multithreaded Coding...
> >>> 
> >>> Good job …
> >>> 
> >>> P. S. if I sent two emails (without questions or question marks inside) in a public forum in the same thread but got no replies, probably it means nobody is interested in the topic or has no time to look into long emails, then I will not send the 3rd email again, I definitely won’t send 10 emails in this case. If I have good project ideas, I would rather try to finish it FIRST, then post a brief news for comments. Hope this helps.
> >>> 
> >>>> 在 12 ott 2017,11:21,David McClain <dbm@refined-audiometrics.com> 写道:
> >>>> 
> >>>> Wow the Walker seems an odd bit of code. There are hints to be found on the copyrights page of the LW manuals, that it dates back to Lucid. And probing on Google brings up ancestor codes from Symbolics and even earlier.
> >>>> 
> >>>> Using the Walker successfully requires forgetting about how you think it should work, and paying attention to how it really is working. Maybe this note can help others, based on what I found by reverse engineering and trial and error.
> >>>> 
> >>>> The Walker basically works with a user provided callback function to which it passes the current subform under inspection, the current environment, and a context. It seems the context is to be ignored. You pass back from the callback routine your modifications to the current subform. That much seems pretty straightforward. The environment is an important piece of the puzzle as it successively records the symbols and kinds of bindings that occur as the Walker probes ever deeper.
> >>>> 
> >>>> But… the Walker will keep throwing your last form right back to you until you return it unchanged. It took a while for that to sink in. So if you perform augmenting rewrites on forms, such as providing nested LET forms inside those present in the subform, then you will go into an infinite loop unless you statefully remember the last form you sent back and compare against the next presented subform. If they are identical, as in EQ, then you should just return it back to the Walker unchanged. Otherwise it represents a new subform for you to chew on.
> >>>> 
> >>>> Once I realized this order in the universe, my lexical binding scanner became massively simplified. No need for markers and cleanup passes to rewrite those markers. Go ahead and augment the subforms handed to you. And using something like Optima MATCH can make life so much more pleasant for finding the subform patterns needing rewriting. Alpha conversion is almost trivial now, except for the fact that lambda arglists must also be alpha converted, lest the arguments refer to extant special bindings (global and otherwise through (DECLARE SPECIAL)).
> >>>> 
> >>>> The bit about it not cleaning up SYMBOL-MACROLET after itself is puzzling, and so I trivially remove the detritus in my second pass. I mark it up to an ancient code base that suffered through many iterations of attempted uniformity against an unruly universe of Lisp providers all going their own way on various aspects of the language.
> >>>> 
> >>>> The Walker is an incredibly useful tool. Too bad so little has been known about it by those of us not members of the pioneer crowd.
> >>>> 
> >>>> Cheers,
> >>>> 
> >>>> - DM
> >>>> 
> >>>> _______________________________________________
> >>>> Lisp Hug - the mailing list for LispWorks users lisp-hug@lispworks.com 
> >>>> http://www.lispworks.com/support/lisp-hug.html
> >>> 
> >>> 
> >>> _______________________________________________
> >>> Lisp Hug - the mailing list for LispWorks users
> >>> lisp-hug@lispworks.com
> >>> http://www.lispworks.com/support/lisp-hug.html
> >>> 
> > 
> > _______________________________________________
> > Lisp Hug - the mailing list for LispWorks users
> > lisp-hug@lispworks.com
> > http://www.lispworks.com/support/lisp-hug.html
> > 
> 
> 

_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Re: Defensive Multithreaded Coding...

Final wrapup… 

The Walker is an insufficient tool, in that it fails to furnish any information about the context in which symbols are seen, meaning TAGBODY tags, BLOCK labels, variable bindings, etc. As a result, attempts to have the Walker assist us to rewrite and augment bindings with inserted known lexical bindings invariably fails in some cases. Rebindings are invented for symbols of unknown binding character, when in fact they are TAGBODY labels. Alpha conversion is similarly hobbled.

I spent a whole day going down the rabbit hole of a recursive descent walker more directly under my own control, and finally stopped in exasperation with its size and complexity. I really don’t want to rewrite a Lisp compiler, and the tool needs to be kept lightweight.

So backtrack… The goal is to avoid accidentally producing code that fails to behave as expected in a foreign thread from where it had been produced, when that code runs just fine in the original thread.

We can very easily have the Walker help us ferret out non-lexical and special symbols, build up a list of such symbols, then wrap the body of code in an idempotent SYMBOL-MACROLET over those symbols like this:
	
	(symbol-macrolet ((x x) (y y) (z z) …)
		… )

This works by performing innoccuous substitutions, and signaling an error if any of the symbols have already been defined with global special bindings. The code to do this is small and simple. Since we just want to know that our code will behave properly in another thread, being told of an error during compile time is okay. At least it won’t blindly produce bad code. Just go back into the package and UNINTERN the offending symbols and try compiling again. Or if you really want to refer to a global binding, just leave its symbol out of the macrolet symbol list.

This shouldn’t have to be a big deal. And it normally wouldn’t be if you are disciplined enough to not play in the same package in which your code has been defined, or if you religiously follow the earmuff convention. I am historically neither. The damning thing is that Lisp entraps you with one-way conversions to special bindings. No way to undo that except by uninterning the symbols.

I suppose an alternative is to wrap the body of code with a block of symbol uninterns. But since that happens silently, you might not like it when you discover you can no longer examine that data you set aside in a global binding. I think being notified by an error signal is probably the better course.

- DM

_______________________________________________
Lisp Hug - the mailing list for LispWorks users
lisp-hug@lispworks.com
http://www.lispworks.com/support/lisp-hug.html

Updated at: 2020-12-10 08:30 UTC