From: ········@gmail.com
Subject: sharp-back syntax
Date: 
Message-ID: <1175215590.880139.160470@y66g2000hsf.googlegroups.com>
I hate having to type l-a-m-b-d-a over and over again...

luckily it's easy to add syntax to Lisp:

(defun sharp-back-var-p (x)
  (when (symbolp x)
    (let ((n (symbol-name x)))
      (when (> (length n) 0)
	(char= (char n 0)
	       #\?)))))

(defun sharp-back-expand (form)
  (let (vs)
    (labels ((rfn (x)
	       (if (sharp-back-var-p x)
		   (pushnew x vs)
		   (when (listp x)
		     (mapc #'rfn x)))))
      (rfn form)
      `(lambda ,(nreverse vs) ,form))))

(set-dispatch-macro-character #\# #\`
			      #'(lambda (s c1 c2)
				  (declare (ignore c1 c2))
				  (sharp-back-expand (read s))))


usage:

#`(> 4 5) => (lambda () (> 4 5))
#`(= ?x 5) => (lambda (?x) (= ?x 5))
#`(print (+ ?a ?b)) => (lambda (?a ?b) (print (+ ?a ?b)))
#`(list ?x ?y ?x ?x ?y) => (lambda (?x ?y) (list ?x ?y ?x ?x ?y)
(mapcar #`(> ?x ?y) list1 list2) => (mapcar (lambda (?x ?y) (> ?x ?y))
list1 list2)

hth

Nick

From: Rob Warnock
Subject: Re: sharp-back syntax
Date: 
Message-ID: <MaSdnbeOX7C4FZHbnZ2dnUVZ_hGdnZ2d@speakeasy.net>
<········@gmail.com> wrote:
+---------------
| I hate having to type l-a-m-b-d-a over and over again...
| luckily it's easy to add syntax to Lisp:
...
| #`(= ?x 5) => (lambda (?x) (= ?x 5))  ...
| (mapcar #`(> ?x ?y) list1 list2) => ...
+---------------

Yeah, I think we've all done something similar. Myself,
I called it #$ and used shell-like ${digit} as params:

    > (mapcar #$(= $1 5) '(1 3 5 7 9))

    (NIL NIL T NIL NIL)
    > (mapcar #$(* $1 1.085) '(12.34 15 10 25.37))

    (13.3889 16.275 10.85 27.52645)
    > (mapcar #$(> $1 $2) '(1 2 3 4 5) '(5 4 3 2 1))

    (NIL NIL NIL T T)
    > (mapcar #$$2 '(1 2 3) '(4 5 6) '(7 8 9))

    (4 5 6)
    >

But I use this *only* at the REPL when poking around,
*never* in saved source files...


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Barry Margolin
Subject: Re: sharp-back syntax
Date: 
Message-ID: <barmar-87FBFC.01230230032007@comcast.dca.giganews.com>
In article <································@speakeasy.net>,
 ····@rpw3.org (Rob Warnock) wrote:

> <········@gmail.com> wrote:
> +---------------
> | I hate having to type l-a-m-b-d-a over and over again...
> | luckily it's easy to add syntax to Lisp:
> ...
> | #`(= ?x 5) => (lambda (?x) (= ?x 5))  ...
> | (mapcar #`(> ?x ?y) list1 list2) => ...
> +---------------
> 
> Yeah, I think we've all done something similar. Myself,
> I called it #$ and used shell-like ${digit} as params:
> 
>     > (mapcar #$(= $1 5) '(1 3 5 7 9))
> 
>     (NIL NIL T NIL NIL)
>     > (mapcar #$(* $1 1.085) '(12.34 15 10 25.37))
> 
>     (13.3889 16.275 10.85 27.52645)
>     > (mapcar #$(> $1 $2) '(1 2 3 4 5) '(5 4 3 2 1))
> 
>     (NIL NIL NIL T T)
>     > (mapcar #$$2 '(1 2 3) '(4 5 6) '(7 8 9))
> 
>     (4 5 6)
>     >
> 
> But I use this *only* at the REPL when poking around,
> *never* in saved source files...

One problem I can see with this is that they don't nest properly.  The 
outer one will drill into inner one and see its implicit lambda 
variables, and make them into lambda varables for the outer one.

Also, if you have any quoted lists that contain symbols in the same 
format as your implicit lambda variables, the reader macro will think 
they're variables.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
*** PLEASE don't copy me on replies, I'll read them in the group ***
From: ········@gmail.com
Subject: Re: sharp-back syntax
Date: 
Message-ID: <1175283293.779691.217500@y80g2000hsf.googlegroups.com>
On Mar 29, 10:23 pm, Barry Margolin <······@alum.mit.edu> wrote:
> In article <································@speakeasy.net>,
>  ····@rpw3.org (Rob Warnock) wrote:
>
>
>
> > <········@gmail.com> wrote:
> > +---------------
> > | I hate having to type l-a-m-b-d-a over and over again...
> > | luckily it's easy to add syntax to Lisp:
> > ...
> > | #`(= ?x 5) => (lambda (?x) (= ?x 5))  ...
> > | (mapcar #`(> ?x ?y) list1 list2) => ...
> > +---------------
>
> > Yeah, I think we've all done something similar. Myself,
> > I called it #$ and used shell-like ${digit} as params:
>
> >     > (mapcar #$(= $1 5) '(1 3 5 7 9))
>
> >     (NIL NIL T NIL NIL)
> >     > (mapcar #$(* $1 1.085) '(12.34 15 10 25.37))
>
> >     (13.3889 16.275 10.85 27.52645)
> >     > (mapcar #$(> $1 $2) '(1 2 3 4 5) '(5 4 3 2 1))
>
> >     (NIL NIL NIL T T)
> >     > (mapcar #$$2 '(1 2 3) '(4 5 6) '(7 8 9))
>
> >     (4 5 6)
>
> > But I use this *only* at the REPL when poking around,
> > *never* in saved source files...
>
> One problem I can see with this is that they don't nest properly.  The
> outer one will drill into inner one and see its implicit lambda
> variables, and make them into lambda varables for the outer one.
>
> Also, if you have any quoted lists that contain symbols in the same
> format as your implicit lambda variables, the reader macro will think
> they're variables.

are you talking about mine or Rob's? Mine doesn't actually rewrite any
code, it just wraps it in a "(lambda list-of-implicit-lambda-vars..."
form so QUOTE will behave normally, so will scope...

now if only Allegro Prolog behaved so nicely with nested forms...

Nick
From: Barry Margolin
Subject: Re: sharp-back syntax
Date: 
Message-ID: <barmar-1DD06D.21470530032007@comcast.dca.giganews.com>
In article <························@y80g2000hsf.googlegroups.com>,
 ········@gmail.com wrote:

> On Mar 29, 10:23 pm, Barry Margolin <······@alum.mit.edu> wrote:
> > In article <································@speakeasy.net>,
> >  ····@rpw3.org (Rob Warnock) wrote:
> >
> >
> >
> > > <········@gmail.com> wrote:
> > > +---------------
> > > | I hate having to type l-a-m-b-d-a over and over again...
> > > | luckily it's easy to add syntax to Lisp:
> > > ...
> > > | #`(= ?x 5) => (lambda (?x) (= ?x 5))  ...
> > > | (mapcar #`(> ?x ?y) list1 list2) => ...
> > > +---------------
> >
> > > Yeah, I think we've all done something similar. Myself,
> > > I called it #$ and used shell-like ${digit} as params:
> >
> > >     > (mapcar #$(= $1 5) '(1 3 5 7 9))
> >
> > >     (NIL NIL T NIL NIL)
> > >     > (mapcar #$(* $1 1.085) '(12.34 15 10 25.37))
> >
> > >     (13.3889 16.275 10.85 27.52645)
> > >     > (mapcar #$(> $1 $2) '(1 2 3 4 5) '(5 4 3 2 1))
> >
> > >     (NIL NIL NIL T T)
> > >     > (mapcar #$$2 '(1 2 3) '(4 5 6) '(7 8 9))
> >
> > >     (4 5 6)
> >
> > > But I use this *only* at the REPL when poking around,
> > > *never* in saved source files...
> >
> > One problem I can see with this is that they don't nest properly.  The
> > outer one will drill into inner one and see its implicit lambda
> > variables, and make them into lambda varables for the outer one.
> >
> > Also, if you have any quoted lists that contain symbols in the same
> > format as your implicit lambda variables, the reader macro will think
> > they're variables.
> 
> are you talking about mine or Rob's? Mine doesn't actually rewrite any
> code, it just wraps it in a "(lambda list-of-implicit-lambda-vars..."
> form so QUOTE will behave normally, so will scope...

I'm talking about both versions.  You have to walk through the code 
looking for the implicit lambda vars, so that you construct the lambda 
list.  But if there are any quoted symbols that look like your implicit 
lambda variables you'll add them to the lambda list.  E.g. I'd expect 
this:

(mapcar #$(eq $1 '$2) '(a b $2 c))

to generate a "wrong number of arguments" error because it will expand 
into:

(mapcar #'(lambda ($1 $2) (eq $1 '$2)) '(a b $2 c))

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
*** PLEASE don't copy me on replies, I'll read them in the group ***
From: ········@gmail.com
Subject: Re: sharp-back syntax
Date: 
Message-ID: <1175308121.426059.83610@y66g2000hsf.googlegroups.com>
> I'm talking about both versions.  You have to walk through the code
> looking for the implicit lambda vars, so that you construct the lambda
> list.  But if there are any quoted symbols that look like your implicit
> lambda variables you'll add them to the lambda list.  E.g. I'd expect
> this:
>
> (mapcar #$(eq $1 '$2) '(a b $2 c))
>
> to generate a "wrong number of arguments" error because it will expand
> into:
>
> (mapcar #'(lambda ($1 $2) (eq $1 '$2)) '(a b $2 c))

ah, right. thanks for pointing that out.

(defun sharp-back-expand (form)
  (let (vs)
    (labels ((rfn (x)
	       (if (sharp-back-var-p x)
		   (pushnew x vs)
		   (when (listp x)
		     (unless (eql (first x) 'quote) ;
		       (mapc #'rfn x))))))
      (rfn form)
      `(lambda ,(nreverse vs) ,form))))
From: Barry Margolin
Subject: Re: sharp-back syntax
Date: 
Message-ID: <barmar-A29962.10421931032007@comcast.dca.giganews.com>
In article <·······················@y66g2000hsf.googlegroups.com>,
 ········@gmail.com wrote:

> > I'm talking about both versions.  You have to walk through the code
> > looking for the implicit lambda vars, so that you construct the lambda
> > list.  But if there are any quoted symbols that look like your implicit
> > lambda variables you'll add them to the lambda list.  E.g. I'd expect
> > this:
> >
> > (mapcar #$(eq $1 '$2) '(a b $2 c))
> >
> > to generate a "wrong number of arguments" error because it will expand
> > into:
> >
> > (mapcar #'(lambda ($1 $2) (eq $1 '$2)) '(a b $2 c))
> 
> ah, right. thanks for pointing that out.
> 
> (defun sharp-back-expand (form)
>   (let (vs)
>     (labels ((rfn (x)
> 	       (if (sharp-back-var-p x)
> 		   (pushnew x vs)
> 		   (when (listp x)
> 		     (unless (eql (first x) 'quote) ;
> 		       (mapc #'rfn x))))))
>       (rfn form)
>       `(lambda ,(nreverse vs) ,form))))

That's not the only place where symbols are not evaluated as variables.

#$(let (($2 1))
    (+ $1 $2)) 

(defmacro my-quote (x) `(quote ,x))

(mapcar #$(eq $1 (my-quote $2)) '(a b $2 c))

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
*** PLEASE don't copy me on replies, I'll read them in the group ***
From: ········@gmail.com
Subject: Re: sharp-back syntax
Date: 
Message-ID: <1175368327.629462.47510@y80g2000hsf.googlegroups.com>
> That's not the only place where symbols are not evaluated as variables.
>
> #$(let (($2 1))
>     (+ $1 $2))
>
> (defmacro my-quote (x) `(quote ,x))
>
> (mapcar #$(eq $1 (my-quote $2)) '(a b $2 c))

I humbly admit you are right...

*sigh*

no good deed goes unpunished on c.l.l.... ;-)
From: Rob Warnock
Subject: Re: sharp-back syntax
Date: 
Message-ID: <xtGdnZalQZIFRZDbnZ2dnUVZ_hadnZ2d@speakeasy.net>
Barry Margolin  <······@alum.mit.edu> wrote:
+---------------
|  ········@gmail.com wrote:
| > are you talking about mine or Rob's? Mine doesn't actually rewrite any
| > code, it just wraps it in a "(lambda list-of-implicit-lambda-vars..."
| > form so QUOTE will behave normally, so will scope...
| 
| I'm talking about both versions.  You have to walk through the code 
| looking for the implicit lambda vars, so that you construct the lambda 
| list.  But if there are any quoted symbols that look like your implicit 
| lambda variables you'll add them to the lambda list.  E.g. I'd expect 
| this:
| 
| (mapcar #$(eq $1 '$2) '(a b $2 c))
| 
| to generate a "wrong number of arguments" error because it will
| expand into:
| 
| (mapcar #'(lambda ($1 $2) (eq $1 '$2)) '(a b $2 c))
+---------------

Nope. It [well, mine at least] expands into this:

  (mapcar (lambda (&optional $1 $2 $3 $4 $5 $6 $7 $8 $9 &rest $*)
            (declare (ignorable $1 $2 $3 $4 $5 $6 $7 $8 $9 $*))
	    (eq $1 '$2))
	  '(a b $2 c))

which works just fine:

    > (mapcar #$(eq $1 '$2) '(a b $2 c))

    (NIL NIL T NIL)
    > 


-Rob

p.s. Yes, I know the "$*" is handled wrong.
It's a hack, what can I say.

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Rob Warnock
Subject: Re: sharp-back syntax
Date: 
Message-ID: <cpKdnU8mZLaUSpDbnZ2dnUVZ_hmtnZ2d@speakeasy.net>
<········@gmail.com> wrote:
+---------------
| Barry Margolin <······@alum.mit.edu> wrote:
| > ····@rpw3.org (Rob Warnock) wrote:
...
| > >     > (mapcar #$(> $1 $2) '(1 2 3 4 5) '(5 4 3 2 1))
| >
| > >     (NIL NIL NIL T T)
| > >     > ...
...
| > > But I use this *only* at the REPL when poking around,
| > > *never* in saved source files...
| >
| > One problem I can see with this is that they don't nest properly.  The
| > outer one will drill into inner one and see its implicit lambda
| > variables, and make them into lambda varables for the outer one.
+---------------

Mine doesn't "drill" at all, it just uses normal lexical scope
with a bunch of fixed pre-chosen optional lambda varables:

;;; SET-SHARP-DOLLAR-READER -- Experimental LAMBDA abbreviation (#1 of 2).
;;; SYNTAX: #$FORM
;;; An abbreviation of: (lambda (&optional $1 $2 $3 $4 $5 $6 $7 $8 $9 &rest $*)
;;;                       FORM)
;;; Within the FORM, args $1 ... $9 and $* are be lambda-bound as positional
;;; and &REST parameters, respectively. Usually, but not always, FORM will be
;;; an S-expr, e.g. #$(car $3), but this is legal: #$FOO ==> (lambda () FOO),
;;; that is, (CONSTANTLY FOO). Likewise, #$$3 ==> #'THIRD.
;;;
;;; As a convenience for interactive use, in the special case that FORM is a
;;; list and (car FORM) is also a list, then an implicit PROGN is provided,
;;; e.g., #$((foo) (bar)) ==> (lambda (args...) (foo) (bar)).
;;;
(defun set-sharp-dollar-reader ()
  (flet ((sharp-dollar-reader (s c p)
           (declare (ignore c p))
           (let* ((form (read s t nil t)))
             `(lambda (&optional $1 $2 $3 $4 $5 $6 $7 $8 $9 &rest $*)
                (declare (ignorable $1 $2 $3 $4 $5 $6 $7 $8 $9 $*))
                ,@(if (and (consp form) (consp (car form)))
                    form
                    (list form))))))
    (set-dispatch-macro-character #\# #\$ #'sharp-dollar-reader)))

So, yes, it suffers from variable capture.

But who cares? I've *never* found a use for nesting them.
As I said, "I use this *only* at the REPL when poking around..."

By the way, here's another style I've tried occasionally.
I don't like it as much, but it doesn't suffer from the
variable capture problem:

    > (mapcar #[x (= x 5)] '(1 3 5 7 9))

    (NIL NIL T NIL NIL)
    > (mapcar #[x (* x 1.085)]  '(12.34 15 10 25.37))

    (13.3889 16.275 10.85 27.52645)
    > (mapcar #[(x y) (> x y)] '(1 2 3 4 5) '(5 4 3 2 1))

    (NIL NIL NIL T T)
    > (mapcar #[&rest (list* 'foo rest)] '(1 2 3) '(4 5 6) '(7 8 9))

    ((FOO 1 4 7) (FOO 2 5 8) (FOO 3 6 9))
    > 

Definition:

;;; SET-SHARP-BRACKET-READER -- Experimental LAMBDA abbreviation (#2 of 2).
;;; SYNTAX: #[ARGS . BODY]
;;; An abbreviation of (LAMBDA args . body), with two special cases
;;; (feel free to change them, your tastes may differ);
;;; 1. If the ARGS sub-form is the symbol &REST (in any package) then the
;;;    form is re-written as (LAMBDA (&rest current-pkg::rest) . body); and
;;; 2. If the ARGS sub-form is any other single symbol then the form is
;;;    re-written as (LAMBDA (args) . body).
;;; Otherwise, the form is simply re-written as (LAMBDA args . body).
;;; Examples:
;;;   (mapcar #[x (1+ x)] list1)
;;;   (mapcar #[(x y) (cons y x)] list1 list2)  ; almost a REV-PAIRLIS
;;;   (mapcar #[&rest (apply #'some-func fixed-arg1 fixed-arg2 rest)] lists...)
;;;
(defun set-sharp-bracket-reader ()
  (macrolet ((ch (x) (char "()[]{}<>"   ; idiom for avoiding editor mismatches
                           (position x '(:lp :rp :lb :rb :lc :rc :la :ra)))))
    (flet ((sharp-bracket-reader (s c p)
             (declare (ignore c p))
             (let* ((args (read s t nil t))
                    (body (read-delimited-list (ch :rb) s t)))
               (etypecase args
                 (symbol                ; special syntax for some common cases
                  (if (equal (symbol-name '&rest) (symbol-name args))
                    `(lambda (&rest ,(intern (symbol-name 'rest))) ,@body)
                    `(lambda (,args) ,@body)))
                 (list
                  `(lambda ,args ,@body))))))
      (set-dispatch-macro-character #\# (ch :lb) #'sharp-bracket-reader)
      (set-macro-character (ch :rb) (get-macro-character (ch :rp) nil)))))

Then there's always this one, which is the same as the previous one
except without the funny reader syntax [and except that it uses a
Scheme-style &REST parameter]:

    > (defmacro fn (args &body body)
        `(lambda ,(if (listp args) args (list '&rest args)) ,@body))

    FN
    > (mapcar (fn (x) (= x 5)) '(1 3 5 7 9))

    (NIL NIL T NIL NIL)
    > (mapcar (fn (x) (* x 1.085))  '(12.34 15 10 25.37))

    (13.3889 16.275 10.85 27.52645)
    > (mapcar (fn (x y) (> x y)) '(1 2 3 4 5) '(5 4 3 2 1))

    (NIL NIL NIL T T)
    > (mapcar (fn x (list* 'foo x)) '(1 2 3) '(4 5 6) '(7 8 9))

    ((FOO 1 4 7) (FOO 2 5 8) (FOO 3 6 9))
    > 

But typing FN isn't much savings over typing LAMBDA, so I don't
use that one much, either.

My #$ readmacro's main win [and its main technical problem] is its
fixed pre-defined parameter list, with the shell-like $1, $2, etc.
If that's not good enough, I just use LAMBDA.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: ··@codeartist.org
Subject: Re: sharp-back syntax
Date: 
Message-ID: <1175248503.810546.191870@p77g2000hsh.googlegroups.com>
On 30 Mrz., 02:46, ········@gmail.com wrote:
> I hate having to type l-a-m-b-d-a over and over again...
>
> luckily it's easy to add syntax to Lisp:
>

yeah - lisp makes this things really easy. I've a similar reader macro
lying around somewhere. I did not really use it though. In some cases
of lambda-heavy code I use a macro called FN which is defined as
follows:

(defmacro fn (ll &body forms)
  (let* ((ignored-symbols nil)
         (ll (mapcar (lambda (v)
                       (if (string-equal '_ v)
                           (let ((v (gensym)))
                              (push v ignored-symbols)
                              v)
                           v))
                     ll)))
  `(lambda ,ll
     ,@(when ignored-symbols
        `((declare (ignore ,@ignored-symbols))))
     ,@forms)))

It's just a thin wrapper around LAMBDA with a shorter name and
automatic ignoring of params which are named "_".

(fn (_ a b _) (+ a b)) ==> (lambda (t1 a b t2) (declare (ignore t1
t2)) (+ a b))

ciao,
Jochen