From: Ampy
Subject: LET improved
Date: 
Message-ID: <1148192340.550085.205580@i39g2000cwa.googlegroups.com>
Hi!
Two things impede me in practical Lisp programming - the prefix
notation for arithmetic expressions (especially, for complex ones) and
lot of parentheses when I just want to declare lexical variable with
`let'. I just wrote such a reader macro to get rid of the latter. How
do you like it?

; allows parenless syntax for let and let*
; inserts let[*] declaration with execution body
; identifier scope is from current position to
; the end of current () block
; new declarations should occur pairwise
; example:
;   (progn
;     #let* i 20 j (+ i 15)
;     (format t "I = ~S J = ~S~%" i j))
(defun read-let (stream char decimal)
 (declare (ignore char decimal))
 (let ((letform (cdr (assoc (read stream) '((et . let) (et* .
let*))))))
   (unless letform
     (cerror "Result is unpredictable" "Illegal char"))
   ;collect pairs of symbol and value for let header
   (do   ((form1 #1=(read stream) #1#) (form2) (letlist))
         ((not (symbolp form1)) (nconc (list letform (nreverse
letlist))
           ;now collect forms of let's body
           (do   ((char #2=(peek-char t stream nil nil) #2#) (bodylist
(list form1)))
                 ((or (null char) (eq char #\))) (nreverse bodylist))
               (if (eq char #\;) (read-line stream)
                   (push (read stream) bodylist)))))
       (setf form2 (read stream))
       (push (list form1 form2) letlist))))

(set-dispatch-macro-character #\# #\l #'read-let)

(progn
  #let* i 20 j (+ i 15)
  #let k 37
  (format t "Hello~%")
  (format t "I = ~S J = ~S K = ~S~%" i j k)
  (format t "It was nice to see you.~%")
;test
)

From: Novus
Subject: Re: LET improved
Date: 
Message-ID: <2006052103245516807-novus@ngoqdeorg>
On 2006-05-21 02:19:00 -0400, "Ampy" <····@users.sourceforge.net> said:

> (progn
>   #let* i 20 j (+ i 15)
>   #let k 37
>   (format t "Hello~%")
>   (format t "I = ~S J = ~S K = ~S~%" i j k)
>   (format t "It was nice to see you.~%")
> ;test
> )

You honestly find that more attractive than the following?

(let* ((i 20)
       (j (+ i 15))
       (k 37))
  (format t "Hello~%")
  (format t "I = ~S J = ~S K = ~S~%" i j k)
  (format t "It was nice to see you.~%"))


I think most uses of reader macros end up being quite ugly.

Novus
From: Ampy
Subject: Re: LET improved
Date: 
Message-ID: <1148204073.581062.252280@y43g2000cwc.googlegroups.com>
I belive it's a matter of habit. I used to find ugly '*' in let* and '
for quote. Standard let in this example has 12 more braces, but that' s
ok. What is difficult in real code is to separate assigned variables
from expressions to be assigned and extra burden of tracing where to
close let variable declaration block and entire let form. Most of time
I end let block as C compiler does - at the the end of current
execution block, so let the lisp reader count parentheses.
From: Bill Atkins
Subject: Re: LET improved
Date: 
Message-ID: <87r72njqwz.fsf@rpi.edu>
"Ampy" <····@users.sourceforge.net> writes:

> ok. What is difficult in real code is to separate assigned variables
> from expressions to be assigned and extra burden of tracing where to
> close let variable declaration block and entire let form. Most of time

This is not difficult.  Get Emacs and load Paredit.  Stop with the
abominations.

-- 
You fool! You fell victim to one of the classic blunders! The most
famous is, "Never get involved in a land war in Asia", but only
slightly less well-known is this: "Never go in against a Sicilian when
death is on the line"!
From: M Jared Finder
Subject: Re: LET improved
Date: 
Message-ID: <foWdneu3wLZg3e3ZnZ2dnUVZ_tKdnZ2d@speakeasy.net>
Ampy wrote:
> Hi!
> Two things impede me in practical Lisp programming - the prefix
> notation for arithmetic expressions (especially, for complex ones) and
> lot of parentheses when I just want to declare lexical variable with
> `let'. I just wrote such a reader macro to get rid of the latter. How
> do you like it?

<snip>

I would guess that it's not the parenthesis that are bothering you so 
much as the extra level of indentation.  You can avoid the extra level 
of indentation without adding a reader macro by writing a binding macro 
that'd be used like this:

(progn
   ;; Bind is implicitly parallel.  If you want order to matter, you
   ;;must use separate bind statements.
   (bind i 20)
   (bind j (+ i 15))
   (bind k 37)
   (format t "Hello~%")
   (format t "I = ~S J= ~S K = ~S~%" i j k)
   (format t "It was nice to see you.~%"))

This is an idea I've been floating around for a while.  With a new 
binding construct, you could do almost all of Common Lisp's bindings 
with just one construct:

(bind i 10                              ; like cl:let
       #'fn (lambda (x) (prin1 x))       ; like cl:flet
       (a (b &optional c)) vals          ; like cl:destructuring-bind
       (values x y z) (values 1 0 0))    ; like multiple-value-bind

There's a slight ambiguity in the syntax between the destructuring-bind 
case and all other special cases, but I doubt it'd be a problem much in 
practice.

   -- MJF
From: Ampy
Subject: Re: LET improved
Date: 
Message-ID: <1148218050.859075.286340@y43g2000cwc.googlegroups.com>
This bind macro is nice, but I really can't see how it could be
programmed without touching lisp system sources.
I'm not aware of C `alloca' equivalent in lisp.
From: M Jared Finder
Subject: Re: LET improved
Date: 
Message-ID: <A4udnd2OCOgVCe3ZnZ2dnUVZ_vqdnZ2d@speakeasy.net>
Ampy wrote:
> This bind macro is nice, but I really can't see how it could be
> programmed without touching lisp system sources.
> I'm not aware of C `alloca' equivalent in lisp.

The great thing about Lisp is that it is relatively easy to provide the 
illusion of being built in without actually being built in.  As you 
point out, bind can not be implemented as a stand alone macro.  But you 
could implement binder::progn as a macro that looks for binder::bind.

;; NOTE: Completely untested code, badly documented code.  I may have
;;gotten many details wrong!
(defpackage :binder)

(defmacro binder::bind (&whole whole &rest args)
   ;; Ideally the documentation here would be programmatically generated
   (declare (ignore args))
   (error "BIND used in an unsupported location ~A" whole))
(export 'binder::bind :binder)

(defun binder::bind-expand (args)
   "A simple version of bind-expand that only supports LET-style binds."
   (format t "~&~A" args)
   (cond
     ((null args) '())
     ((symbolp (car args))
      (cons (car args) (binder::bind-expand (cdr args))))
     ((eq 'binder:bind (caar args))
      `((let ,(loop for var in (cdar args) by #'cddr
                 and value in (cdr (cdar args)) by #'cddr
                 collect (list var value))
          ,@(binder::bind-expand (cdr args)))))
     (t (cons (car args) (binder::bind-expand (cdr args))))))

(shadow 'binder::progn :binder)
(defmacro binder::progn (&rest args)
   "Replacement for cl:progn that supports BIND"
   `(cl:progn ,@(binder::bind-expand args)))
(export 'binder::bind :binder)
;; Do the same sort of thing to every other construct...

   -- MJF
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148273159.857762.164690@j73g2000cwa.googlegroups.com>
> The great thing about Lisp is that it is relatively easy to provide the
> illusion of being built in without actually being built in.  As you
> point out, bind can not be implemented as a stand alone macro.  But you
> could implement binder::progn as a macro that looks for binder::bind.

Well, I'd name it a hack with illusion that there's no hack (the job
that wasn't supposed to look like a job? :-). My macro at least do not
mislead human code reader - it's a hack that looks like a hack. Thanks
for an example, I had a chance to play with shadowing a little:

[9]> (load "binder")
;; Loading file C:\WORK\AMPY\lisp\tests\binder.lisp ...
;; Loaded file C:\WORK\AMPY\lisp\tests\binder.lisp
T
[10]> (defpackage "MYOWN" (:use "CL" "BINDER") (:shadowing-import-from
"BINDER" binder::progn))
#<PACKAGE MYOWN>
[11]> (in-package "MYOWN")
#<PACKAGE MYOWN>
MYOWN[12]> (symbol-package 'progn)
#<PACKAGE BINDER>
MYOWN[13]> (let ((i 2)) (progn (bind j (+ i 1)) (print j)))
((BIND J (+ I 1)) (PRINT J))
((PRINT J))
NIL
3
3

;unfortunately, bind isn't recognized in each 'implicit progn' place

MYOWN[14]> (defun foo(i) (bind j (+ i 1)) (print j))

*** - BIND used in an unsupported location (BIND J (+ I 1))
The following restarts are available:
ABORT          :R1      ABORT
Break 1 MYOWN[15]> :a
From: M Jared Finder
Subject: Re: LET improved
Date: 
Message-ID: <0JGdnVLuetwLK-_ZnZ2dnUVZ_tidnZ2d@speakeasy.net>
Arseny Slobodyuk wrote:
>> The great thing about Lisp is that it is relatively easy to provide the
>> illusion of being built in without actually being built in.  As you
>> point out, bind can not be implemented as a stand alone macro.  But you
>> could implement binder::progn as a macro that looks for binder::bind.
> 
> Well, I'd name it a hack with illusion that there's no hack (the job
> that wasn't supposed to look like a job? :-). My macro at least do not
> mislead human code reader - it's a hack that looks like a hack. Thanks
> for an example, I had a chance to play with shadowing a little:

That's what Common Lisp macros are all about -- making hacks that don't 
look like hacks. ;)  After all, if it doesn't look like a hack, and 
doesn't act like a hack, it must not be a hack.

> [9]> (load "binder")
> ;; Loading file C:\WORK\AMPY\lisp\tests\binder.lisp ...
> ;; Loaded file C:\WORK\AMPY\lisp\tests\binder.lisp
> T
> [10]> (defpackage "MYOWN" (:use "CL" "BINDER") (:shadowing-import-from
> "BINDER" binder::progn))
> #<PACKAGE MYOWN>
> [11]> (in-package "MYOWN")
> #<PACKAGE MYOWN>
> MYOWN[12]> (symbol-package 'progn)
> #<PACKAGE BINDER>
> MYOWN[13]> (let ((i 2)) (progn (bind j (+ i 1)) (print j)))
> ((BIND J (+ I 1)) (PRINT J))
> ((PRINT J))
> NIL
> 3
> 3
> 
> ;unfortunately, bind isn't recognized in each 'implicit progn' place
> 
> MYOWN[14]> (defun foo(i) (bind j (+ i 1)) (print j))
> 
> *** - BIND used in an unsupported location (BIND J (+ I 1))
> The following restarts are available:
> ABORT          :R1      ABORT
> Break 1 MYOWN[15]> :a

You gonna let that get in your way?  It's simple enough to extend BIND 
to support all the relevant symbols in CL.  As a hint, here's some 
slight changes so that it now supports defun.

   -- MJF

;;;; bind.lisp -- The BIND form talked about on C.L.L.
(defpackage bind
   (:documentation "Package for the BIND form.")
   (:export :bind :add-bind-block :remove-bind-block :bind-expand)
   (:use :cl))
(in-package bind)

(defparameter *bind-documentation-format*
   "An extendable replacement for CL:LET, CL:FLET, and such.

See ADD-BIND-BLOCK REMOVE-BIND-BLOCK, and DEFINE-BIND-FORM.

Examples:
   (bind a 1 b 2)                ; the same as (let ((a 1) (b 2)) ...)
   (bind #'fn (lambda (arg) arg) ; the same as (flet ((fn (arg) arg)) ...)
   (bind (values a b) (fn)       ; the same as (multiple-value-bind (a 
b) (fn) ...)

The following forms support BIND:~{~&  ~S~}")

(defmacro bind (&whole whole &rest name-value-pairs)
   ;; Documentation is programatically generated by 
UPDATE-BIND-DOCUMENTATION
   (declare (ignore name-value-pairs))
   (error "BIND used in an unsported location: ~A" whole))

(defvar *bind-forms* '()
   "A collection of forms that support BIND.")

(defun bind-expand (args)
   "A simple version of bind-expand that only supports LET-style binds."
   (cond
     ((null args) '())
     ((atom (car args))
      (cons (car args) (bind::bind-expand (cdr args))))
     ((eq 'bind:bind (caar args))
      ;; Don't want to expand into bind:let; that'd cause infinite 
recursion!
      `((cl:let ,(loop for var in (cdar args) by #'cddr
                    and value in (cdr (cdar args)) by #'cddr
                    collect (list var value))
          ,@(bind::bind-expand (cdr args)))))
     (t (cons (car args) (bind::bind-expand (cdr args))))))

(defun bind-forms-sorter (sym1 sym2)
   (cond
     ((eq (symbol-package sym1) (symbol-package sym2))
      (string< (symbol-name sym1) (symbol-name sym2)))
     ((eq (symbol-package sym1) (find-package :bind))
      t)
     (t
      (string< (package-name (symbol-package sym1))
               (package-name (symbol-package sym2))))))

(defun update-bind-documentation ()
   (setf (documentation 'bind 'function)
         (let ((*package* (find-package :keyword)))
           (format nil *bind-documentation-format* *bind-forms*))))

(defun add-bind-block (form expander
                        &optional (new-form (intern (symbol-name form) 
:bind)))
   "Add NEW-FORM as a variant of FORM that supports BIND, and return 
NEW-FORM.

EXPANDER is a function that takes the body of a call to FORM and
substitutes (BIND-EXPAND body) for each appropriate body"
   (eval `(let ((expander ,expander))
            (defmacro ,new-form (&rest args)
              ,(let ((*package* (find-package :keyword)))
                    (format nil "Replacement for ~S that supports ~S" 
form 'bind))
              `(,',form ,@(funcall expander args)))))
   (setf *bind-forms* (sort (union (list new-form) *bind-forms*) 
#'bind-forms-sorter))
   (update-bind-documentation)
   new-form)

(defun remove-bind-block (form)
   "Remove FORM as a form that supports BIND"
   (fmakunbound form)
   (setf *bind-forms* (delete form *bind-forms*))
   (update-bind-documentation))

(add-bind-block 'progn (lambda (forms) (bind-expand forms)))
(add-bind-block 'defun (lambda (forms)
                          (append (subseq forms 0 2)
                                  (bind-expand (subseq forms 2)))))
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148440492.570210.230330@38g2000cwa.googlegroups.com>
> You gonna let that get in your way?  It's simple enough to extend BIND
> to support all the relevant symbols in CL.  As a hint, here's some
> slight changes so that it now supports defun.

Now it looks like a whole facility :-)
Well, I'll stay with my reader macro, improved even more.
#let was stupid. Now I'm thinking about
#% clform rest
where clform can be let[*], [multiple-value/destructuring]-bind or
something else.
It will just mechanically rearrange the code, not checking what form is
given.
I'm planning to leave surrounding braces in variable declaration, I
think I can live with it, you was right.
From: Alexander Schmolck
Subject: Re: LET improved
Date: 
Message-ID: <yfshd3jmth0.fsf@oc.ex.ac.uk>
M Jared Finder <·····@hpalace.com> writes:

> Ampy wrote:
> > Hi!
> > Two things impede me in practical Lisp programming - the prefix
> > notation for arithmetic expressions (especially, for complex ones) and
> > lot of parentheses when I just want to declare lexical variable with
> > `let'. I just wrote such a reader macro to get rid of the latter. How
> > do you like it?
> 
> <snip>
> 
> I would guess that it's not the parenthesis that are bothering you so much as
> the extra level of indentation. You can avoid the extra level of indentation
> without adding a reader macro by writing a binding macro that'd be used like
> this:

What is (BIND K 9) supposed to expand to so that (PROGN (BIND K 9) K) will
yield 9?

> (progn
>    ;; Bind is implicitly parallel.  If you want order to matter, you
>    ;;must use separate bind statements.
>    (bind i 20)
>    (bind j (+ i 15))
>    (bind k 37)
>    (format t "Hello~%")
>    (format t "I = ~S J= ~S K = ~S~%" i j k)
>    (format t "It was nice to see you.~%"))
> 
> This is an idea I've been floating around for a while. With a new binding
> construct, you could do almost all of Common Lisp's bindings with just one
> construct:
> 
> 
> (bind i 10                              ; like cl:let
>        #'fn (lambda (x) (prin1 x))       ; like cl:flet

I think it ought to be recursive (i.e. like labels), because it is pretty rare
that you'd like the outer binding of FN to be accessible in the body, whereas
recursive helper functions are pretty common.

>        (a (b &optional c)) vals          ; like cl:destructuring-bind

I think I'd favor something like:

 (lambda-list a (b &optional c)) vals

or the more general, but more involved:

 (quasiquote ,a (,b ,@(maybe c))) vals

(This would only need trivial read macros; the nicer `(,a (,b ,@(maybe c)))
would be a right pain). 
 

>        (values x y z) (values 1 0 0))    ; like multiple-value-bind
> 
> There's a slight ambiguity in the syntax between the destructuring-bind case
> and all other special cases, but I doubt it'd be a problem much in practice.

I don't like that, as it would also mean that the BIND construct is less
extensible. I'd favor SYMBOL | (BINDING-TYPE . REST) on the LHS. I'd also like
the ability to mix the various types of bindings and add type-annotations, for
(a stupid) example:

(bind (values #'fn (quasiquote ,a (,b ,(the fixnum i)))) 
      #'sin '(1 (2 3)))


'as
From: Marco Baringer
Subject: Re: LET improved
Date: 
Message-ID: <m2wtcfs5yd.fsf@bese.it>
M Jared Finder <·····@hpalace.com> writes:

> This is an idea I've been floating around for a while.  With a new
> binding construct, you could do almost all of Common Lisp's bindings
> with just one construct:
>
> (bind i 10                              ; like cl:let
>       #'fn (lambda (x) (prin1 x))       ; like cl:flet
>       (a (b &optional c)) vals          ; like cl:destructuring-bind
>       (values x y z) (values 1 0 0))    ; like multiple-value-bind
>
> There's a slight ambiguity in the syntax between the
> destructuring-bind case and all other special cases, but I doubt it'd
> be a problem much in practice.

i've also had a similar idea (though my main problem was indentation,
not a distaste for let and friends). i came up with a WITH macro:

(with
  (let ((i 10)))
  (flet ((fn (x) (prin1 x))))
  (destructuring-bind (a (b &optional c)) vals)
  (multiple-value-bind (x y z) (values 1 0 0))

  (progn
    (do-stuff-here)
    ...))

the implemention of with is trivial:

(defmacro with* (&body body)
  (cond
    ((cddr body)
     (append (first body) `((with* ,@(cdr body)))))
    ((cdr body)
     `(,@(first body) ,(second body)))
    (body (first body))
    (t nil)))

this macro also plays nice with things like with-open-file and friends.

-- 
-Marco
Ring the bells that still can ring.
Forget the perfect offering.
There is a crack in everything.
That's how the light gets in.
	-Leonard Cohen
From: Rainer Joswig
Subject: Re: LET confused
Date: 
Message-ID: <joswig-FA0EA3.12440921052006@news-europe.giganews.com>
In article <························@i39g2000cwa.googlegroups.com>,
 "Ampy" <····@users.sourceforge.net> wrote:

> Hi!
> Two things impede me in practical Lisp programming - the prefix
> notation for arithmetic expressions (especially, for complex ones) and
> lot of parentheses when I just want to declare lexical variable with
> `let'. I just wrote such a reader macro to get rid of the latter. How
> do you like it?

Not at all.

> ; allows parenless syntax for let and let*
> ; inserts let[*] declaration with execution body
> ; identifier scope is from current position to
> ; the end of current () block
> ; new declarations should occur pairwise
> ; example:
> ;   (progn
> ;     #let* i 20 j (+ i 15)
> ;     (format t "I = ~S J = ~S~%" i j))
> (defun read-let (stream char decimal)
>  (declare (ignore char decimal))
>  (let ((letform (cdr (assoc (read stream) '((et . let) (et* .
> let*))))))
>    (unless letform
>      (cerror "Result is unpredictable" "Illegal char"))
>    ;collect pairs of symbol and value for let header
>    (do   ((form1 #1=(read stream) #1#) (form2) (letlist))
>          ((not (symbolp form1)) (nconc (list letform (nreverse
> letlist))
>            ;now collect forms of let's body
>            (do   ((char #2=(peek-char t stream nil nil) #2#) (bodylist
> (list form1)))
>                  ((or (null char) (eq char #\))) (nreverse bodylist))
>                (if (eq char #\;) (read-line stream)
>                    (push (read stream) bodylist)))))
>        (setf form2 (read stream))
>        (push (list form1 form2) letlist))))
> 
> (set-dispatch-macro-character #\# #\l #'read-let)
> 
> (progn
>   #let* i 20 j (+ i 15)
>   #let k 37
>   (format t "Hello~%")
>   (format t "I = ~S J = ~S K = ~S~%" i j k)
>   (format t "It was nice to see you.~%")
> ;test
> )

Maybe Python is better for you?

-- 
http://lispm.dyndns.org/
From: Pascal Bourguignon
Subject: Re: LET improved
Date: 
Message-ID: <87r72nbbbb.fsf@thalassa.informatimago.com>
"Ampy" <····@users.sourceforge.net> writes:

> Hi!
> Two things impede me in practical Lisp programming - the prefix
> notation for arithmetic expressions (especially, for complex ones) and
> lot of parentheses when I just want to declare lexical variable with
> `let'. I just wrote such a reader macro to get rid of the latter. How
> do you like it?

You're still a parentheses counter, not a lisp programmer.  ;-)

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

"A TRUE Klingon warrior does not comment his code!"
From: Ampy
Subject: Re: LET improved
Date: 
Message-ID: <1148267843.148877.196910@38g2000cwa.googlegroups.com>
> You're still a parentheses counter, not a lisp programmer.  ;-)
Why I become a better lisp programmer when I make emacs count my
parentheses and not lisp reader?
From: Rob Thorpe
Subject: Re: LET improved
Date: 
Message-ID: <1148301499.723847.62120@j73g2000cwa.googlegroups.com>
Ampy wrote:
> > You're still a parentheses counter, not a lisp programmer.  ;-)
> Why I become a better lisp programmer when I make emacs count my
> parentheses and not lisp reader?

If you write lisp programs the normal way then they are easier to
understand by other lisp programmers.  Using your own syntax for
superficial things makes the barrier to understanding higher for other.
 This goes for any language.

It is also easier to understand the effect, and to write macros if the
textual source is similar to the tree it corresponds to.  Given the
two:-
> (progn
>   #let* i 20 j (+ i 15)
>   #let k 37
>   (format t "Hello~%")
>   (format t "I = ~S J = ~S K = ~S~%" i j k)
>   (format t "It was nice to see you.~%")
> ;test
> )

and

> (let* ((i 20)
>         (j (+ i 15))
>         (k 37))
>   (format t "Hello~%")
>   (format t "I = ~S J = ~S K = ~S~%" i j k)
>   (format t "It was nice to see you.~%"))

It is clearer in the later
1)what the tree looks like
2)how this code could be used in a macro, and
3)how a macro would act on this code (eg how let* could be replaced by
something else by the programmer).

Other languages than lisp have allowed the programmer to manipulate the
parse tree and write complex macros.  But very few people actually use
it because the syntax of the source language brings it so far from the
underlying tree it makes writing macros fraught with peril.
From: Duane Rettig
Subject: Re: LET improved
Date: 
Message-ID: <o0bqtq84v4.fsf@franz.com>
"Ampy" <····@users.sourceforge.net> writes:

>> You're still a parentheses counter, not a lisp programmer.  ;-)

> Why I become a better lisp programmer when I make emacs count my
> parentheses and not lisp reader?

Because when you become a lisp programmer [sic] the parentheses
disappear, and you can then move beyond obscessing about syntax and
concentrate on writing your programs.  The parentheses are a pain,
until they disappear for you, and then they become the unseen ether
that holds the lisp universe together.

(for the group):

Perhaps this is the "secret handshake" of lisp programming; perhaps
whenever someone says "I am a lisp programmer", the assertion can be
sanity-checked by asking the person "Do you see the parentheses?"...

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: Pascal Costanza
Subject: Re: LET improved
Date: 
Message-ID: <4de3itF1a6e82U1@individual.net>
Duane Rettig wrote:
> "Ampy" <····@users.sourceforge.net> writes:
> 
>>> You're still a parentheses counter, not a lisp programmer.  ;-)
> 
>> Why I become a better lisp programmer when I make emacs count my
>> parentheses and not lisp reader?
> 
> Because when you become a lisp programmer [sic] the parentheses
> disappear, and you can then move beyond obscessing about syntax and
> concentrate on writing your programs.  The parentheses are a pain,
> until they disappear for you, and then they become the unseen ether
> that holds the lisp universe together.
> 
> (for the group):
> 
> Perhaps this is the "secret handshake" of lisp programming; perhaps
> whenever someone says "I am a lisp programmer", the assertion can be
> sanity-checked by asking the person "Do you see the parentheses?"...

...and the correct response would be: "What parentheses?" ;)


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148441043.269818.280740@38g2000cwa.googlegroups.com>
"There's no parentheses, Neo!"

Thank's, I'll remember it :-)
From: Frank Buss
Subject: Re: LET improved
Date: 
Message-ID: <xt26jrmi0tvd$.f9nie3ufb2fz.dlg@40tude.net>
Ampy wrote:

> Two things impede me in practical Lisp programming - the prefix
> notation for arithmetic expressions (especially, for complex ones)

There is an infix package at
http://www-cgi.cs.cmu.edu/afs/cs/project/ai-repository/ai/lang/lisp/code/syntax/infix/0.html
for reading infix expressions, but the licence says:

;;; Use and copying of this software and preparation of derivative works
;;; based upon this software are permitted, so long as the following
;;; conditions are met:
;;;      o no fees or compensation are charged for use, copies, 
;;;        distribution or access to this software

so it could be difficult to include it in commercial programs. And it looks
way too complicated, at least for me, which was the reason for the version
below, which can be used for whatever you want (think BSD licence style)
and which is easy to enhance. You can use it like this:


CL-USER > (infix "1+2")
(+ 1 2)

CL-USER > (infix "99*x^5-0.1*x^2+abc*sin(x^(y-1))")
(+ (- (* 99 (EXPT X 5)) (* 0.1 (EXPT X 2))) (* ABC (SIN (EXPT X (- Y 1)))))

CL-USER > (loop for x from 0 to 3 collect #i "2*x^2+3*x-5")
(-5 0 9 22)


This is the source:


(defmacro defun-eval-recursive (function next-function char-function-list)
  `(defun ,function (stream)
     (let ((value (,next-function stream)))
       (loop do
         (let ((c (peek-char t stream nil nil)))
           (if c
               (cond
                ,@(loop for (char function) in char-function-list collect
                        `((char= c ,char)
                          (read-char stream)
                          (setf value
                                `(,',function ,value
                                              ,(,next-function stream)))))
                (t (loop-finish)))
             (loop-finish))))
       value)))

(defun-eval-recursive eval-infix eval-product ((#\+ +) (#\- -)))

(defun-eval-recursive eval-product eval-expt ((#\* *) (#\/ /)))

(defun-eval-recursive eval-expt eval-unary ((#\^ expt)))

(defun eval-unary (stream)
  (if (check-char stream #\-)
      `(- ,(eval-primary stream))
    (eval-primary stream)))

(defun eval-primary (stream)
  (if (check-char stream #\()
      (let ((value (eval-infix stream)))
        (expect stream #\))
        value)
    (let ((symbol-string
           (with-output-to-string (out)
             (loop for c = (peek-char nil stream nil nil) do
                   (unless (and c (or (alphanumericp c)
                                      (char= c #\.)))
                     (loop-finish))
                   (write-char c out)
                   (read-char stream)))))
      (with-input-from-string (s symbol-string)
        (let ((symbol (read s)))
          (if (and (alphanumericp (elt symbol-string 0))
                   (check-char stream #\())
              (let ((function-argument (eval-infix stream)))
                (expect stream #\))
                `(, symbol ,function-argument))
            symbol))))))

(defun expect (stream char)
  (unless (check-char stream char)
    (error (format nil "~a expected" char))))

(defun check-char (stream char)
  (let ((c (peek-char t stream nil nil)))
    (when (and c (char= c char))
      (read-char stream))))

(defun infix (string)
  (with-input-from-string (s string)
    (eval-infix s)))

(defun read-infix (stream subchar arg)
  (declare (ignore subchar arg))
  (expect stream #\")
  (prog1
      (eval-infix stream)
    (expect stream #\")))

(set-dispatch-macro-character #\# #\i #'read-infix)

(defun test ()
  (let ((tests '(("1" 1)
                 ("1+2" (+ 1 2))
                 ("-1+(-2*3)" (+ (- 1) (* (- 2) 3)))
                 ("2+3*4/5^x" (+ 2 (/ (* 3 4) (expt 5 x))))
                 ("1.5e2*10 + cos(x)" (+ (* 150.0 10) (cos x))))))
    (loop for (string expected) in tests do
          (assert (equalp (infix string) expected)))))

-- 
Frank Buss, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148275118.947454.40760@y43g2000cwc.googlegroups.com>
Frank Buss wrote:

> way too complicated, at least for me, which was the reason for the version
> below, which can be used for whatever you want (think BSD licence style)

Damn, I wanted to finally make it myself.
Thanks! But again, why do not use reader macros?
In the flamewars with C apologists, lispers always mention their
ability to change lisp syntax. And then when one wants to actually fit
the syntax to his needs he is told that reader macros are ugly.
From: Rainer Joswig
Subject: Re: LET improved, time wasted
Date: 
Message-ID: <C0972968.3D83E%joswig@lisp.de>
Am 22.05.2006 7:18 Uhr schrieb "Arseny Slobodyuk" unter
<····@users.sourceforge.net> in
·······················@y43g2000cwc.googlegroups.com:

> 
> Frank Buss wrote:
> 
>> way too complicated, at least for me, which was the reason for the version
>> below, which can be used for whatever you want (think BSD licence style)
> 
> Damn, I wanted to finally make it myself.
> Thanks! But again, why do not use reader macros?
> In the flamewars with C apologists, lispers always mention their
> ability to change lisp syntax. And then when one wants to actually fit
> the syntax to his needs he is told that reader macros are ugly.
> 
 

Common Lisp provides you all the necessary tools to shoot yourself into your
foot. But there is actually nothing in Common Lisp that claims it to be a
good idea to do so.

My advice for all people wanting to learn programming in Common Lisp (I
really hope that's a goal for some and not just to play around):

   Don't try to change Common Lisp in the first two years you use Common
Lisp.

The first steps towards Common Lisp should not be to 'improve' it. Learn to
live with the basics of the language and try to write some more useful code.
That you can change Common Lisp does NOT mean you should start with it.

Especially beginners should try to follow this list:

- don't write reader macros to 'beautify' the language
- don't invent a new 'simpler' programming language on top of Common Lisp
- don't change the case of SYMBOLS
- don't try to write a new symbol and package system
- don't write a new object system to replace or 'enhance' CLOS
- don't use EVAL
- don't try to make Common Lisp a Lisp-1
- don't invent a new syntax
- don't add new special forms
- don't add or replace functionality in the package "COMMON-LISP"
- don't invent a new Common Lisp standard
- avoid macrology

There is not much point in doing the above 'experiments', unless you have
some experience and some real need for it. Most of it is a waste of time.
Really.

Believe me, you can write lots of useful software in plain old LISP. Tons.
Easy.

People, don't concentrate on starting with Lisp with micro/macro changes to
Common Lisp. Instead try to learn programming in Common Lisp by writing
programs. Useful starting points are the books by Peter Seibel and Peter
Norvig (PAIP).

Like in every programming language there is good and bad style. Don't start
with bad style.

Here is some introduction to good Common Lisp programming styles. Probably
it's better to read that, instead of trying to 'improve' Common Lisp.

   http://www.norvig.com/luv-slides.ps
From: Arseny Slobodyuk
Subject: Re: LET improved, time wasted
Date: 
Message-ID: <1148299036.568743.111040@u72g2000cwu.googlegroups.com>
> Believe me, you can write lots of useful software in plain old LISP. Tons.
> Easy.

Well, I (ocasonally) write Lisp code since past century (you'll say
`AND LEARNED NOTHING!') and find Lisp much more convenient for certain
tasks than C/C++, or, say, it's better to make something with Lisp than
in electronic spreadsheet. And all this time I wonder, why can't I
declare new lexical variable in the middle of (procedural) execution
block in Lisp as I do it in C++. More precisely, I realized that it's
related to C++ just for now, but had the feeling since beginning. If
you don't become used to it, you won't miss it.

The slides are inspiring indeed. I heat my read-let implementation
already.
From: Thomas A. Russ
Subject: Re: LET improved, time wasted
Date: 
Message-ID: <ymimzd9lndu.fsf@sevak.isi.edu>
"Arseny Slobodyuk" <····@users.sourceforge.net> writes:
>  And all this time I wonder, why can't I
> declare new lexical variable in the middle of (procedural) execution
> block in Lisp as I do it in C++. 

Of course you can.  The syntax is just a bit different.

> More precisely, I realized that it's
> related to C++ just for now, but had the feeling since beginning. If
> you don't become used to it, you won't miss it.

For example you could do the following:

(let ((a 10)
      (b 100))
  (print a)
  (print b)
  (let ((sum (+ a b)))
     (print sum)
     (print b)
     (print sum)))

This introduces SUM in the middle of the execution block, somewhat
similar to the C++

{int a = 10;
 int b = 100;
 cout << a << endl;
 cout << b << endl;
 int sum = a + b;
 cout << sum << endl;
 cout << b << endl;
 cout << sum << endl;
}

The only real difference is that you get additional indentation from
the lisp form.  One can argue about various style issues here, but in a
very long procedural form, it can be rather difficult to visually locate
the introduction of lexical variables is they are actually distributed
throughout the code with no particular visual cues.

Personally, I prefer to put all variables up at the head, so that they
are easy to find for code reading and maintenance, but there are other
styles available, so...

-- 
Thomas A. Russ,  USC/Information Sciences Institute
From: Peter Seibel
Subject: Re: LET improved, time wasted
Date: 
Message-ID: <m2zmharv2o.fsf@gigamonkeys.com>
Rainer Joswig <······@lisp.de> writes:

> Am 22.05.2006 7:18 Uhr schrieb "Arseny Slobodyuk" unter
> <····@users.sourceforge.net> in
> ·······················@y43g2000cwc.googlegroups.com:
>
>> 
>> Frank Buss wrote:
>> 
>>> way too complicated, at least for me, which was the reason for the version
>>> below, which can be used for whatever you want (think BSD licence style)
>> 
>> Damn, I wanted to finally make it myself.
>> Thanks! But again, why do not use reader macros?
>> In the flamewars with C apologists, lispers always mention their
>> ability to change lisp syntax. And then when one wants to actually fit
>> the syntax to his needs he is told that reader macros are ugly.
>> 
>  
>
> Common Lisp provides you all the necessary tools to shoot yourself into your
> foot. But there is actually nothing in Common Lisp that claims it to be a
> good idea to do so.
>
> My advice for all people wanting to learn programming in Common Lisp (I
> really hope that's a goal for some and not just to play around):
>
>    Don't try to change Common Lisp in the first two years you use Common
> Lisp.
>
> The first steps towards Common Lisp should not be to 'improve' it. Learn to
> live with the basics of the language and try to write some more useful code.
> That you can change Common Lisp does NOT mean you should start with it.
>
> Especially beginners should try to follow this list:
>
> - don't write reader macros to 'beautify' the language
> - don't invent a new 'simpler' programming language on top of Common Lisp
> - don't change the case of SYMBOLS
> - don't try to write a new symbol and package system
> - don't write a new object system to replace or 'enhance' CLOS
> - don't use EVAL
> - don't try to make Common Lisp a Lisp-1
> - don't invent a new syntax
> - don't add new special forms
> - don't add or replace functionality in the package "COMMON-LISP"
> - don't invent a new Common Lisp standard
> - avoid macrology

A great list though I disagree with the last one. Macros are an
important part of the language that a proficient Lisper has to learn
to use with style and grace. I say, go for it and use them now,
without style and without grace; you're going to have to do it some
time. But you should be working toward understanding when they are
appropriate. Maybe you should not worry about macros for the first two
days or first two weeks of your Lisp career, just to make sure you get
a grip on the basics of the rest of the language but two years is way
too long to wait.

Another metric to tell whether you're ready to attempt any of the
things on Ranier's list is: if you think it's unambiguously a good
idea you're not ready. ;-)

> There is not much point in doing the above 'experiments', unless you have
> some experience and some real need for it. Most of it is a waste of time.
> Really.
>
> Believe me, you can write lots of useful software in plain old LISP. Tons.
> Easy.
>
> People, don't concentrate on starting with Lisp with micro/macro changes to
> Common Lisp. Instead try to learn programming in Common Lisp by writing
> programs. Useful starting points are the books by Peter Seibel and Peter
> Norvig (PAIP).

At least one of whose authors, I happen to know, went to some pains to
introduce the appropriate use of macros fairly early on on the book.

-Peter

-- 
Peter Seibel           * ·····@gigamonkeys.com
Gigamonkeys Consulting * http://www.gigamonkeys.com/
Practical Common Lisp  * http://www.gigamonkeys.com/book/
From: Rainer Joswig
Subject: Re: LET improved, time wasted
Date: 
Message-ID: <C097B8D3.3D988%joswig@lisp.de>
Am 22.05.2006 16:30 Uhr schrieb "Peter Seibel" unter <·····@gigamonkeys.com>
in ··············@gigamonkeys.com:

> Rainer Joswig <······@lisp.de> writes:
> 
>> Am 22.05.2006 7:18 Uhr schrieb "Arseny Slobodyuk" unter
>> <····@users.sourceforge.net> in
>> ·······················@y43g2000cwc.googlegroups.com:
>> 
>>> 
>>> Frank Buss wrote:
>>> 
>>>> way too complicated, at least for me, which was the reason for the version
>>>> below, which can be used for whatever you want (think BSD licence style)
>>> 
>>> Damn, I wanted to finally make it myself.
>>> Thanks! But again, why do not use reader macros?
>>> In the flamewars with C apologists, lispers always mention their
>>> ability to change lisp syntax. And then when one wants to actually fit
>>> the syntax to his needs he is told that reader macros are ugly.
>>> 
>>  
>> 
>> Common Lisp provides you all the necessary tools to shoot yourself into your
>> foot. But there is actually nothing in Common Lisp that claims it to be a
>> good idea to do so.
>> 
>> My advice for all people wanting to learn programming in Common Lisp (I
>> really hope that's a goal for some and not just to play around):
>> 
>>    Don't try to change Common Lisp in the first two years you use Common
>> Lisp.
>> 
>> The first steps towards Common Lisp should not be to 'improve' it. Learn to
>> live with the basics of the language and try to write some more useful code.
>> That you can change Common Lisp does NOT mean you should start with it.
>> 
>> Especially beginners should try to follow this list:
>> 
>> - don't write reader macros to 'beautify' the language
>> - don't invent a new 'simpler' programming language on top of Common Lisp
>> - don't change the case of SYMBOLS
>> - don't try to write a new symbol and package system
>> - don't write a new object system to replace or 'enhance' CLOS
>> - don't use EVAL
>> - don't try to make Common Lisp a Lisp-1
>> - don't invent a new syntax
>> - don't add new special forms
>> - don't add or replace functionality in the package "COMMON-LISP"
>> - don't invent a new Common Lisp standard
>> - avoid macrology
> 
> A great list though I disagree with the last one. Macros are an
> important part of the language that a proficient Lisper has to learn
> to use with style and grace.

What I meant was using macros as a special science and macros for the
purpose of having macros. As I said in another post, if you can do it with
functions, then use functions. If you can't do it with functions, try
harder. If you then still think functions are not the right thing, then use
macros. After you have a solution with macros, try to rewrite it with
functions. ;-) Functions are easier to replace and debug. Lots. Really.

What I always hate is when stuff is not first class, not reflective and not
late binding. This always creates trouble in maintenance. Try to build
maintainable architectures. A macro is always less maintainable then the
equivalent function. If beginners think they should start with digging a
very deep hole, I really like to point out that you need a story how to get
out of this hole at some point. Also you should think first if you really
really need the deep hole. ;-)

Macrology: See http://www.jargon.net/jargonfile/m/macrology.html

Especially bad (-> hard to debug and maintain) are macros that generate
other macros or macros that depend on side effects at compile time.

I know I have been guilty, too. But don't say you haven't been warned. ;-)

> I say, go for it and use them now,
> without style and without grace; you're going to have to do it some
> time. But you should be working toward understanding when they are
> appropriate. Maybe you should not worry about macros for the first two
> days or first two weeks of your Lisp career, just to make sure you get
> a grip on the basics of the rest of the language but two years is way
> too long to wait.
> 
> Another metric to tell whether you're ready to attempt any of the
> things on Ranier's list is: if you think it's unambiguously a good
> idea you're not ready. ;-)
> 
>> There is not much point in doing the above 'experiments', unless you have
>> some experience and some real need for it. Most of it is a waste of time.
>> Really.
>> 
>> Believe me, you can write lots of useful software in plain old LISP. Tons.
>> Easy.
>> 
>> People, don't concentrate on starting with Lisp with micro/macro changes to
>> Common Lisp. Instead try to learn programming in Common Lisp by writing
>> programs. Useful starting points are the books by Peter Seibel and Peter
>> Norvig (PAIP).
> 
> At least one of whose authors, I happen to know, went to some pains to
> introduce the appropriate use of macros fairly early on on the book.
From: Frank Buss
Subject: Re: LET improved
Date: 
Message-ID: <1q1u35vp4q3ng.v2ktx289thez.dlg@40tude.net>
Arseny Slobodyuk wrote:

> Damn, I wanted to finally make it myself.
> Thanks! But again, why do not use reader macros?
> In the flamewars with C apologists, lispers always mention their
> ability to change lisp syntax. And then when one wants to actually fit
> the syntax to his needs he is told that reader macros are ugly.

I'm not sure what you mean. The CLHS says in
http://www.lisp.org/HyperSpec/Body/glo_r.html#reader_macro that a reader
macro is what I've defined with #i, but you could implement it like this,
too:

(defun read-infix-reader (stream char)
  (declare (ignore char))
  (prog1
      (eval-infix stream)
    (expect stream #\])))

(set-macro-character #\[ 'read-infix-reader)

Then you could use it like this:

CL-USER > (let ((x 2)) [x^2+x^3])
12

-- 
Frank Buss, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148299087.801540.207380@j73g2000cwa.googlegroups.com>
Oops, sorry. I didn't looked yet into the code closely, just reviewed
the examples.
From: Mikalai
Subject: Re: LET improved
Date: 
Message-ID: <1148495027.869932.213120@g10g2000cwb.googlegroups.com>
Ampy wrote:
> Hi!
> Two things impede me in practical Lisp programming - the prefix
> notation for arithmetic expressions (especially, for complex ones) and
> lot of parentheses when I just want to declare lexical variable with
> `let'. I just wrote such a reader macro to get rid of the latter. How
> do you like it?

Try TwinLisp ( http://twinlisp.nongnu.org/ ). These annoying things go
away. Just try TL.

For an example, I'll rewrite in TL your code:
> (progn
>   #let* i 20 j (+ i 15)
>   #let k 37
>   (format t "Hello~%")
>   (format t "I = ~S J = ~S K = ~S~%" i j k)
>   (format t "It was nice to see you.~%")
> ;test
> )

as:

progn {
  i=20
  j=i+15
  k=37
  cout() << "Hello~%"
  cout() << "I = ~S J = ~S K = ~S~%" % [i,j,k]
  cout() << "It was nice to see you.~%" }
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148562419.827454.214210@u72g2000cwu.googlegroups.com>
> Try TwinLisp ( http://twinlisp.nongnu.org/ ). These annoying things go
> away. Just try TL.
I talked about two small things in Lisp, not that I heat Lisp syntax!
One needs serious reasons to learn a new language.
From: Novus
Subject: Re: LET improved
Date: 
Message-ID: <2006052519215716807-novus@ngoqdeorg>
On 2006-05-25 09:06:59 -0400, "Arseny Slobodyuk" 
<····@users.sourceforge.net> said:

>> Try TwinLisp ( http://twinlisp.nongnu.org/ ). These annoying things go
>> away. Just try TL.
> I talked about two small things in Lisp, not that I heat Lisp syntax!
> One needs serious reasons to learn a new language.

One needs serious reasons to learn a new language well enough to write a
large application in it. Given that there will never be the "one true
language" I would hope that one needs very little reason to at least check
out what a new language offers and why.

Novus
From: Arseny Slobodyuk
Subject: Re: LET improved
Date: 
Message-ID: <1148604606.556740.326440@y43g2000cwc.googlegroups.com>
> One needs serious reasons to learn a new language well enough to write a
> large application in it. Given that there will never be the "one true
> language" I would hope that one needs very little reason to at least check
> out what a new language offers and why.

Actually I checked it out, and would like to say something positive
about it, aside from it's a plenty of work put in it... There is a nice
website, a tutorial (very important for such a thing), the system is
carefully tested (there's large bunch of tests in the distribution).
But I don't like the idea.