From: Tayssir John Gabbour
Subject: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <866764be.0406261117.1ae88721@posting.google.com>
Here LET surrounds a DEFUN for little obvious reason, which is not
explained:

(let ((rpar (get-macro-character #\) )))
  (defun ddfn (left right fn)
    (set-macro-character right rpar)
    (set-dispatch-macro-character #\# left
                                  #'(lambda (stream char1 char2)
                                      (apply fn
                                             (read-delimited-list
right stream t))))))

I can only guess that someone might find it a tiny bit easier to
change rpar's definition.

But in that case, there should be some function which allows one to
modify rpar. As the code stands, the let is mystifying. I even find it
hard to read, since I keep looking around for DDFN's "missing"
definition.

Maybe he intended to put other DEFUNs in the LET's lexical context,
and just got rushed?

From: Pascal Bourguignon
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <87eko22i94.fsf@thalassa.informatimago.com>
···········@yahoo.com (Tayssir John Gabbour) writes:

> Here LET surrounds a DEFUN for little obvious reason, which is not
> explained:
> 
> (let ((rpar (get-macro-character #\) )))
>   (defun ddfn (left right fn)
>     (set-macro-character right rpar)
>     (set-dispatch-macro-character #\# left
>                                   #'(lambda (stream char1 char2)
>                                       (apply fn
>                                              (read-delimited-list
> right stream t))))))
> 
> I can only guess that someone might find it a tiny bit easier to
> change rpar's definition.
> 
> But in that case, there should be some function which allows one to
> modify rpar. As the code stands, the let is mystifying. I even find it
> hard to read, since I keep looking around for DDFN's "missing"
> definition.
> 
> Maybe he intended to put other DEFUNs in the LET's lexical context,
> and just got rushed?

The meaning of this (let (...) (defun ...))  is that rpar is the
macro-character value of #\) AT THE TIME OF THE DEFINITION of the
function ddfn.

Probably, ulterior code will change the macro-character for #\), and
as you can see, this ddfn depends on the original macro-character
value of #\0.

Another way to write it would have been to use (defparameter ..)
(defun...)  but in that case, any random evil code could modify the
value of the variable defined by defparameter, while with the (let
(...) (defun ...)), the rpar is enclosed in the closure and
unaccessible from the rest of the code.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

There is no worse tyranny than to force a man to pay for what he does not
want merely because you think it would be good for him. -- Robert Heinlein
From: Tayssir John Gabbour
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <866764be.0406261759.2adaa029@posting.google.com>
Pascal Bourguignon <····@thalassa.informatimago.com> wrote in message news:<··············@thalassa.informatimago.com>...
> > Maybe he intended to put other DEFUNs in the LET's lexical context,
> > and just got rushed?
> 
> The meaning of this (let (...) (defun ...))  is that rpar is the
> macro-character value of #\) AT THE TIME OF THE DEFINITION of the
> function ddfn.
> 
> Probably, ulterior code will change the macro-character for #\), and
> as you can see, this ddfn depends on the original macro-character
> value of #\0.
> 
> Another way to write it would have been to use (defparameter ..)
> (defun...)  but in that case, any random evil code could modify the
> value of the variable defined by defparameter, while with the (let
> (...) (defun ...)), the rpar is enclosed in the closure and
> unaccessible from the rest of the code.

You're right, and I felt pretty stupid for not pointing that out after
I posted, but OTOH I would be extremely surprised that lispers go
around modifying )'s error-throwing behaviour. Graham should've given
a warning that this should be expected.

After posting (google groups is slow to update), I wished I mentioned
possible reasons:
a) Speed
b) Proof against (get-macro-character #\) ever changing, since the
value is stored.
c) Readability advantage in not having a defun visible sticking out.

a) seems absurd in this macro-defining context. b) struck me as weird,
but maybe I just don't have enough experience. c) makes sense, but
there are % conventions for this, or use of LABELS.
From: Tim Bradshaw
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <fbc0f5d1.0406280212.db6d0f3@posting.google.com>
Pascal Bourguignon <····@thalassa.informatimago.com> wrote in message news:<··············@thalassa.informatimago.com>...

> 
> Another way to write it would have been to use (defparameter ..)
> (defun...)  but in that case, any random evil code could modify the
> value of the variable defined by defparameter, while with the (let
> (...) (defun ...)), the rpar is enclosed in the closure and
> unaccessible from the rest of the code.

A much clearer way to write something like this is:

(defun foo (...)
  (let ((x (load-time-value ...)))
    ... use x ...)
From: Kalle Olavi Niemitalo
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <87zn6npfl3.fsf@Astalo.kon.iki.fi>
··········@tfeb.org (Tim Bradshaw) writes:

> A much clearer way to write something like this is:
>
> (defun foo (...)
>   (let ((x (load-time-value ...)))
>     ... use x ...)

Suppose that definition is either typed in the REPL, or loaded 
from a source file with LOAD without being compiled.  At least 
CLISP 2.32 will then evaluate the subform of LOAD-TIME-VALUE each 
time FOO is called.  In the GET-MACRO-CHARACTER case, the effect 
is rather unfortunate.  The version with LET around DEFUN avoids 
this problem.

Does this behavior of CLISP not conform to the standard?
From: Christophe Rhodes
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <sq3c4f1ikl.fsf@cam.ac.uk>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> [ load-time-value in non-compiled code ]
> Does this behavior of CLISP not conform to the standard?

I believe CLISP is conforming here.

Christophe
-- 
http://www-jcsu.jesus.cam.ac.uk/~csr21/       +44 1223 510 299/+44 7729 383 757
(set-pprint-dispatch 'number (lambda (s o) (declare (special b)) (format s b)))
(defvar b "~&Just another Lisp hacker~%")    (pprint #36rJesusCollegeCambridge)
From: Tim Bradshaw
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <ey3acyncgzu.fsf@cley.com>
* Kalle Olavi Niemitalo wrote:

> Suppose that definition is either typed in the REPL, or loaded from a
> source file with LOAD without being compiled.  At least CLISP 2.32
> will then evaluate the subform of LOAD-TIME-VALUE each time FOO is
> called.  In the GET-MACRO-CHARACTER case, the effect is rather
> unfortunate.  The version with LET around DEFUN avoids this problem.

> Does this behavior of CLISP not conform to the standard?

Yes, it does.

On the other hand, if you reload a compiled file, both versions will
multiply evaluate the form, anyway.  If you *really* need to protect
against this, then you need to work harder.

I don't like to use (LET (...) (DEFUN ...)) when I can avoid it
because it typically breaks source-finding mechanisms, will often
prevent the function being compiled with COMPILE if you define the
function in the interpreter (REPL or loaded as source), and also
function definition is not at top-level which can have obscure and
exciting effects (and has exposed obscure and exciting implementation
bugs in at least CMUCL).

--tim
From: Kalle Olavi Niemitalo
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <87659a3l36.fsf@Astalo.kon.iki.fi>
Tim Bradshaw <···@cley.com> writes:

> On the other hand, if you reload a compiled file, both versions will
> multiply evaluate the form, anyway.  If you *really* need to protect
> against this, then you need to work harder.

In the On Lisp case, I think (get-macro-character #\) nil) would
be a nice workaround: don't get the macro from the current
readtable, but instead from the standard readtable, which is
supposed to be never modified.
From: Joerg Hoehle
Subject: Re: Reason for let..defun idiom
Date: 
Message-ID: <u3c3w9mj1.fsf_-_@users.sourceforge.net>
Hi,

I wonder how load-time-value may differ from the typical
defun-as-closure introduced by let..defun.

I wonder whether there may be compiler or threading issues.

E.g. consider these variations of code.

(let ((cache (make-hash-table)))
  (defun memo1 (k)		; LET..DEFUN
    (multiple-value-bind (x found) (gethash k cache)
      (cond (found t)
            (t (setf (gethash k cache) k) nil)))))
  
(defun memo2 (k)		; LOAD-TIME-VALUE
  (let ((cache (load-time-value (princ (make-hash-table)))))
    (multiple-value-bind (x found) (gethash k cache)
      (cond (found t)
            (t (setf (gethash k cache) k) nil)))))
  
(defun memo3 (k)		; Using #.
  (let ((cache '#.(make-hash-table)))
    (multiple-value-bind (x found) (gethash k cache)
      (cond (found t)
            (t (setf (gethash k cache) k) nil)))))

(defmacro memo4-writer ()	; "Preprocessing" code
  ;; Note: macro maybe needs eval-when?
  ;; Don't use #. because of *READ-EVAL* but still preprocess code,
  ;; which allows substitutions in places typically not evaluated,
  ;; e.g. type declarations
  (let ((cache (make-hash-table)))
    `(defun memo4 (k)
       (multiple-value-bind (x found) (gethash k ,cache)
         (cond (found t)
               (t (setf (gethash k ,cache) k) nil))))))
(memo4-writer)


Arguments I've heard:

- let..defun causes indentation, thus text-based source analysis
  mechanisms (e.g. TAGS) won't find the defun [T.Bradshaw].
  Work-around: deindent by hand.

+ let..defun allows multiple defuns, whereas neither LOAD-TIME-VALUE
  nor #. do.

+ LOAD-TIME-VALUE does not prevent multiple evaluation while in an
  interpreter [K.O.Niemital] -- this is conformant behaviour
  [T.Bradshaw]  As a result, memo2 won't work there!

- compiled code (in CLISP) is shorter for memo2/3/4 than memo1.

~ memo4 is ugly, an idea of mine as to how to get rid of some
  #.+SOME-CONSTANT-VALUE+ forms people sometimes use in code.

Questions

o Does LOAD-TIME-VALUE prevent a compiler's type inference about the
  resulting value?  I.e., in MEMO2 above, can it prove that table is a
  hash table?
  -- in the let..defun case, it can.

o Is #.(make-hash-table) a correct form in source code
  w.r.t. compilation and externalization of constants?
  -- I'm ignoring security issues about *READ-EVAL*.

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Kalle Olavi Niemitalo
Subject: Re: Reason for let..defun idiom
Date: 
Message-ID: <87wu177kfb.fsf@Astalo.kon.iki.fi>
Joerg Hoehle <······@users.sourceforge.net> writes:

> + LOAD-TIME-VALUE does not prevent multiple evaluation while in an
>   interpreter [K.O.Niemital]

(defmacro* with-string-as-buffer (string-place &rest body &environment env)
  (multiple-value-bind (temps vals new setter getter)
      (get-setf-method string-place env)
    `(with-temp-buffer
       (let ,(mapcar* #'list temps vals)
	 (insert ,getter)
	 ,@body
	 (multiple-value-bind ,new (values (buffer-string))
	   ,setter)))))

;; `macro-declaration-function' doesn't work with `defmacro*'.
(put 'with-string-as-buffer 'lisp-indent-function 1)
(def-edebug-spec with-string-as-buffer (place body))

(with-string-as-buffer gnus-summary-line-format
  (let ((case-fold-search nil))
    (goto-char (point-min))
    (while (search-forward "%-20,20n" nil t)
      (replace-match "%-21,21n" t t))))
From: Tim Bradshaw
Subject: Re: Reason for let..defun idiom
Date: 
Message-ID: <fbc0f5d1.0407140446.6d84d288@posting.google.com>
Joerg Hoehle <······@users.sourceforge.net> wrote in message news:<················@users.sourceforge.net>...

> 
> - let..defun causes indentation, thus text-based source analysis
>   mechanisms (e.g. TAGS) won't find the defun [T.Bradshaw].
>   Work-around: deindent by hand.
> 
> 

The body of a LET is not at top level.  This alters compilation
semantics: read the spec for how.

--tim
From: Joerg Hoehle
Subject: load-time-value type inference (was: Reason for let..defun idiom)
Date: 
Message-ID: <u8ydk8i7o.fsf_-_@users.sourceforge.net>
Hi,

I wondered
Joerg Hoehle <······@users.sourceforge.net> writes:
> o Does LOAD-TIME-VALUE prevent a compiler's type inference about the
>   resulting value?  I.e., in MEMO2 above, can it prove that table is a
>   hash table?
>   -- in the let..defun case, it can.
and got a private response saying the're no reason that
LOAD-TIME-VALUE prevents type inference (if the compiler does some).

Somehow I was under the impression (misconception) that the form in
(LOAD-TIME-VALUE form) would be evaluated at load-time, and not
become compiled. Without compilation, no type inference would occur.

CLHS however says
:the compiler performs its normal semantic processing (such as macro
:expansion and translation into machine code) on form, [...]

So a type-inferencing compiler should know that (load-time-value
(make-hash-table)) yields a hash-table and may optimize based on that.

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Rob Warnock
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <OfWdncZDJqeYaULdRVn-ig@speakeasy.net>
Pascal Bourguignon  <····@thalassa.informatimago.com> wrote:
+---------------
| ···········@yahoo.com (Tayssir John Gabbour) writes:
| > Here LET surrounds a DEFUN for little obvious reason, which is not
| > explained:
| > 
| > (let ((rpar (get-macro-character #\) )))
| >   (defun ddfn (left right fn)
| >     (set-macro-character right rpar)
| >     (set-dispatch-macro-character #\# left
| >                                   #'(lambda (stream char1 char2)
| >                                       (apply fn
| >                                              (read-delimited-list
| > right stream t))))))
...
| The meaning of this (let (...) (defun ...))  is that rpar is the
| macro-character value of #\) AT THE TIME OF THE DEFINITION of the
| function ddfn.
+---------------

In that case, another way to have done it would have been this:

      (defun ddfn (left right fn)
        (set-macro-character right (load-time-value
				    (get-macro-character #\))))
        (set-dispatch-macro-character #\# left
	                              #'(lambda (stream char1 char2)
	                                  (apply fn (read-delimited-list
						     right
						     stream
						     t))))))

Or, if you know the code's being compiled [so that the LET & FLET
will get inlined], I'd prefer this:

      (defun ddfn (left right fn)
	(let ((rpar (load-time-value (get-macro-character #\)))))
	  (flet ((left-func (stream char1 char2)
		   (apply fn (read-delimited-list right stream t))))
	    (set-macro-character right rpar)
	    (set-dispatch-macro-character #\# left left-func))))


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Alex Drummond
Subject: Re: Reason for let..defun idiom in _On Lisp_ code?
Date: 
Message-ID: <cbkkk6$313k$1@uns-a.ucl.ac.uk>
Perhaps it's because the return value of get-macro-character would 
change if the read table changes, and he doesn't want that behaviour. 
I'm just guessing though; it seems quite obscure.

Alex

Tayssir John Gabbour wrote:
> Here LET surrounds a DEFUN for little obvious reason, which is not
> explained:
> 
> (let ((rpar (get-macro-character #\) )))
>   (defun ddfn (left right fn)
>     (set-macro-character right rpar)
>     (set-dispatch-macro-character #\# left
>                                   #'(lambda (stream char1 char2)
>                                       (apply fn
>                                              (read-delimited-list
> right stream t))))))
> 
> I can only guess that someone might find it a tiny bit easier to
> change rpar's definition.
> 
> But in that case, there should be some function which allows one to
> modify rpar. As the code stands, the let is mystifying. I even find it
> hard to read, since I keep looking around for DDFN's "missing"
> definition.
> 
> Maybe he intended to put other DEFUNs in the LET's lexical context,
> and just got rushed?