From: Slobodan Blazeski
Subject: How to simulate currying?
Date: 
Message-ID: <17737c2f-9c7d-4b73-b6d2-31c28c86337e@g1g2000pra.googlegroups.com>
I want to make bind symbol _ to represent omitteed parameter so I
could make automatical currying using CLOS, all methods are of fixed
arity. So far I did this:

(defclass blank () ())
(defconstant _ (make-instance 'blank))

(defmethod plus ((x blank) (y number))
   (lambda (n) (+ n y)))

(defmethod plus ((x number) (y blank))
   (lambda (n) (+ x n)))

(funcall (plus 2 _) 3)
5

Though it works is there is some more elegant way? Preferably without
making class for one lousy symbol.

cheers
bobi

From: Vsevolod
Subject: Re: How to simulate currying?
Date: 
Message-ID: <0663f1d9-b358-44b8-b9c7-5debc0413630@a39g2000prl.googlegroups.com>
On Feb 15, 1:29 am, Slobodan Blazeski <·················@gmail.com>
wrote:
> I want to make bind symbol _ to represent omitteed parameter so I
> could make automatical currying using CLOS, all methods are of fixed
> arity. So far I did this:
>
> (defclass blank () ())
> (defconstant _ (make-instance 'blank))
>
> (defmethod plus ((x blank) (y number))
>    (lambda (n) (+ n y)))
>
> (defmethod plus ((x number) (y blank))
>    (lambda (n) (+ x n)))
>
> (funcall (plus 2 _) 3)
> 5
>
> Though it works is there is some more elegant way? Preferably without
> making class for one lousy symbol.
>
> cheers
> bobi

For this purpose I have a reader macro, that implements what's present
in Arc and Closure -- automatic variable substitution for one-argument
lambdas. It's not, strictly speaking, currying, but it works for most
of the practical cases (I use it very often):

(set-dispatch-macro-character #\# #\`
   (lambda (stream subchar arg)
     (declare (ignore subchar)
              (ignore arg))
     (let ((sexp (read stream t nil t))
           (x (gensym)))
       `(lambda (,x)
          ,@(subst x '_ (if (listp (car sexp)) sexp (list sexp)))))))

So you get (funcall #`(plus 2 _) 3)
A good feature is that it resembles (and thus reminds of) the simple
function reader macro (#')...

Regards,
Vsevolod
From: Slobodan Blazeski
Subject: Re: How to simulate currying?
Date: 
Message-ID: <8f13c24c-c7ee-4209-99b7-e1694209fb61@c12g2000yqj.googlegroups.com>
On Feb 15, 1:00 am, Vsevolod <········@gmail.com> wrote:
> On Feb 15, 1:29 am, Slobodan Blazeski <·················@gmail.com>
> wrote:
>
>
>
>
>
> > I want to make bind symbol _ to represent omitteed parameter so I
> > could make automatical currying using CLOS, all methods are of fixed
> > arity. So far I did this:
>
> > (defclass blank () ())
> > (defconstant _ (make-instance 'blank))
>
> > (defmethod plus ((x blank) (y number))
> >    (lambda (n) (+ n y)))
>
> > (defmethod plus ((x number) (y blank))
> >    (lambda (n) (+ x n)))
>
> > (funcall (plus 2 _) 3)
> > 5
>
> > Though it works is there is some more elegant way? Preferably without
> > making class for one lousy symbol.
>
> > cheers
> > bobi
>
> For this purpose I have a reader macro, that implements what's present
> in Arc and Closure -- automatic variable substitution for one-argument
> lambdas. It's not, strictly speaking, currying, but it works for most
> of the practical cases (I use it very often):
>
> (set-dispatch-macro-character #\# #\`
>    (lambda (stream subchar arg)
>      (declare (ignore subchar)
>               (ignore arg))
>      (let ((sexp (read stream t nil t))
>            (x (gensym)))
>        `(lambda (,x)
>           ,@(subst x '_ (if (listp (car sexp)) sexp (list sexp)))))))
>
> So you get (funcall #`(plus 2 _) 3)
> A good feature is that it resembles (and thus reminds of) the simple
> function reader macro (#')...
>
> Regards,
> Vsevolod
Looks interesthing, will try it thanks.

cheers
bobi
From: Rob Warnock
Subject: Re: How to simulate currying?
Date: 
Message-ID: <irSdnfbYI8d5UgXUnZ2dnUVZ_gudnZ2d@speakeasy.net>
Vsevolod <········@gmail.com> wrote:
+---------------
| Slobodan Blazeski <·················@gmail.com> wrote:
| > I want to make bind symbol _ to represent omitteed parameter so I
| > could make automatical currying using CLOS...
...
| For this purpose I have a reader macro, that implements what's present
| in Arc and Closure -- automatic variable substitution for one-argument
| lambdas. It's not, strictly speaking, currying, but it works for most
| of the practical cases (I use it very often):
|   (set-dispatch-macro-character #\# #\` ...[etc]... )
| So you get (funcall #`(plus 2 _) 3)
| A good feature is that it resembles (and thus reminds of) the simple
| function reader macro (#')...
+---------------

This seems to be a common meme!!  ;-}  My version of this hack
[appended below], which I too use very often in the REPL [but *NEVER*
in code files!!], is much more gross, but gives you up to nine args
plus a &REST arg, flagging both the reader macro and the args with "$"
[in homage to the Bourne Shell], e.g.:

    > (mapcar #$(/ $2 $1) '(1 2 3 4 5 6) '#1=(60 . #1#))

    (60 30 20 15 12 10)
    > 

The main reason I prefer it to a multiple-"_" style which some poeple
have proposed is that you can re-order the args as you choose [as above],
which also makes it convenient as a shorthand for simple instances of
DESTRUCTURING-BIND, e.g. (#$$3 12 34 56 78) ==> 56. It's also a shorthand
for CONSTANTLY:

    > (mapcar #$17.2 '(1 2 3 4) '#1=(60 . #1#))

    (17.2 17.2 17.2 17.2)
    > 

Its biggest current shortcoming is that the &REST arg "$*" [again,
copied from the Bourne Shell] only applies to args greater than "$9".

There was a long discussion thread here on this very topic a while
back [sorry, I don't remember when] in which it was proposed that
[and someone may have even posted code for!] the macro should do a
full tree walk of its body and collect both the highest "${n}" in the
code and also whether "$*" were used. That way, #$(list* $4 $1 $*)
would expand to:

    (lambda ($1 $2 $3 $4 &rest $*)
      (declare (ignore $2 $3))    ; or simpler, (ignorable $1 $2 $3 $4 $*)
	(list* $4 $1 $*))

Unfortunately, I don't remember when that better version was proposed
[or by whom], so all I have is my own crude hack [which I nevertheless
very often find useful when noodling around in the REPL]:

;;; SET-SHARP-DOLLAR-READER -- Experimental LAMBDA abbreviation
;;; SYNTAX: #$FORM
;;; Abbreviates (lambda (&optional $1 $2 $3 $4 $5 $6 $7 $8 $9 &rest $*) FORM)
;;; Within the FORM, args $1 ... $9 and $* are 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)))

Enjoy.(?)  ;-}


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Marcus Breiing
Subject: Re: How to simulate currying?
Date: 
Message-ID: <amas9c2vhamuj@breiing.com>
* Vsevolod

> For this purpose I have a reader macro, that implements what's present
> in Arc and Closure -- automatic variable substitution for one-argument
> lambdas. It's not, strictly speaking, currying, but it works for most
> of the practical cases (I use it very often):

I use similarly Arc-ish syntactic sugar for single-argument,
single-body-form LAMBDAs. Your example would read as

  (funcall #[plus 2 _] 3)

I'm only rarely tempted to extend the syntax to more than one
argument. The point of such syntax, for me, is avoiding LAMBDA forms
when they'd have a large ratio of boilerplate to content. Multi-form
and multi-argument functions tend to be longer, so LAMBDA boilerplate
ceases to be as distracting as it is for trivial functions.

The only other bit of custom reader syntax I use is even more trivial,
but I find it remedies all the Lisp-2 pain, leaving us with only the
advantages of Lisp-2: Replace (funcall f x y) with [f x y]. The
crucial readability difference (that only a reader macro can achieve)
is that the function remains in "function position" within the form.

Code:

(set-dispatch-macro-character #\# #\[
  (lambda (stream char n)
    (declare (ignore char n))
    (let ((_ (intern "_")))
      `(lambda (,_)
         (declare (ignorable ,_))
         ,(read-delimited-list #\] stream 't)))))

(set-macro-character #\[ 
  (lambra (stream char)
  (declare (ignore char))
  `(,(intern "FUNCALL") ,@(read-delimited-list #\] stream 't))))
From: Vsevolod
Subject: Re: How to simulate currying?
Date: 
Message-ID: <d5609455-e2ee-46e3-9063-6d55fd60b10f@f20g2000yqg.googlegroups.com>
On Feb 16, 1:52 pm, Marcus Breiing <······@2009w07.mail.breiing.com>
wrote:
>   (funcall #[plus 2 _] 3)
>
> I'm only rarely tempted to extend the syntax to more than one
> argument. The point of such syntax, for me, is avoiding LAMBDA forms
> when they'd have a large ratio of boilerplate to content. Multi-form
> and multi-argument functions tend to be longer, so LAMBDA boilerplate
> ceases to be as distracting as it is for trivial functions.
I agree, that for a case of multiple arguments such "shortcut" has a
lot of disadvantages, so it's simpler just to stick to the regular
lambda form. The only exception I can think of is the 2-argument
functions, that operate on key-value pairs: it's a common pattern and
they are also often rather short. But I couldn't come up with a good
pair of symbols...

>
> The only other bit of custom reader syntax I use is even more trivial,
> but I find it remedies all the Lisp-2 pain, leaving us with only the
> advantages of Lisp-2: Replace (funcall f x y) with [f x y]. The
> crucial readability difference (that only a reader macro can achieve)
> is that the function remains in "function position" within the form.
I like funcall, its main virtue for me is outlining, where the
function-value of a symbol is used. Your macro does the same in this
regard, but I think it doesn't solve the problem for those, who prefer
Lisp-1: it seems to me, that they don't like even the fact, that you
need to single out (and, generally, think of the distinction between)
functions vs regular vars.

Cheers,
Vsevolod
From: Slobodan Blazeski
Subject: Re: How to simulate currying?
Date: 
Message-ID: <ee1b51c1-4a24-4fcb-8047-d121e3641ec1@g38g2000yqd.googlegroups.com>
On Feb 16, 12:52 pm, Marcus Breiing <······@2009w07.mail.breiing.com>
wrote:
> * Vsevolod
>
> > For this purpose I have a reader macro, that implements what's present
> > in Arc and Closure -- automatic variable substitution for one-argument
> > lambdas. It's not, strictly speaking, currying, but it works for most
> > of the practical cases (I use it very often):
>
> I use similarly Arc-ish syntactic sugar for single-argument,
> single-body-form LAMBDAs. Your example would read as
>
>   (funcall #[plus 2 _] 3)
>
> I'm only rarely tempted to extend the syntax to more than one
> argument. The point of such syntax, for me, is avoiding LAMBDA forms
> when they'd have a large ratio of boilerplate to content. Multi-form
> and multi-argument functions tend to be longer, so LAMBDA boilerplate
> ceases to be as distracting as it is for trivial functions.
>
> The only other bit of custom reader syntax I use is even more trivial,
> but I find it remedies all the Lisp-2 pain, leaving us with only the
> advantages of Lisp-2: Replace (funcall f x y) with [f x y]. The
> crucial readability difference (that only a reader macro can achieve)
> is that the function remains in "function position" within the form.
>
> Code:
>
> (set-dispatch-macro-character #\# #\[
>   (lambda (stream char n)
>     (declare (ignore char n))
>     (let ((_ (intern "_")))
>       `(lambda (,_)
>          (declare (ignorable ,_))
>          ,(read-delimited-list #\] stream 't)))))
>
> (set-macro-character #\[
>   (lambra (stream char)
>   (declare (ignore char))
>   `(,(intern "FUNCALL") ,@(read-delimited-list #\] stream 't))))
All those reader macros are great, but syntax is just discusting. Any
idea how to make some extended defun that will automagically create
curried definitions, or that will be too much work?

cheers
bobi
From: André Thieme
Subject: Re: How to simulate currying?
Date: 
Message-ID: <gnfggf$gsh$1@news.motzarella.org>
Slobodan Blazeski schrieb:
> On Feb 16, 12:52 pm, Marcus Breiing <······@2009w07.mail.breiing.com>
> wrote:
>> * Vsevolod
>>
>>> For this purpose I have a reader macro, that implements what's present
>>> in Arc and Closure -- automatic variable substitution for one-argument
>>> lambdas. It's not, strictly speaking, currying, but it works for most
>>> of the practical cases (I use it very often):
>> I use similarly Arc-ish syntactic sugar for single-argument,
>> single-body-form LAMBDAs. Your example would read as
>>
>>   (funcall #[plus 2 _] 3)
>>
>> I'm only rarely tempted to extend the syntax to more than one
>> argument. The point of such syntax, for me, is avoiding LAMBDA forms
>> when they'd have a large ratio of boilerplate to content. Multi-form
>> and multi-argument functions tend to be longer, so LAMBDA boilerplate
>> ceases to be as distracting as it is for trivial functions.
>>
>> The only other bit of custom reader syntax I use is even more trivial,
>> but I find it remedies all the Lisp-2 pain, leaving us with only the
>> advantages of Lisp-2: Replace (funcall f x y) with [f x y]. The
>> crucial readability difference (that only a reader macro can achieve)
>> is that the function remains in "function position" within the form.
>>
>> Code:
>>
>> (set-dispatch-macro-character #\# #\[
>>   (lambda (stream char n)
>>     (declare (ignore char n))
>>     (let ((_ (intern "_")))
>>       `(lambda (,_)
>>          (declare (ignorable ,_))
>>          ,(read-delimited-list #\] stream 't)))))
>>
>> (set-macro-character #\[
>>   (lambra (stream char)
>>   (declare (ignore char))
>>   `(,(intern "FUNCALL") ,@(read-delimited-list #\] stream 't))))
> All those reader macros are great, but syntax is just discusting. Any
> idea how to make some extended defun that will automagically create
> curried definitions, or that will be too much work?

It�s not possible.
I wanted to implement implicit currying two years ago and found that
it can not be done in the presence of functions that can take any number
of args.
If you see:  (* 3 4), should this then return 12 or
(lambda (&rest args) (apply #'* 3 4 args)) ?
You can not differentiate between these two cases.

I wrote a macro similar to what Rob mentioned, with the $1, $2 and so
on, but also supporting the underscore syntax.

[rgb _ _ 255] returns a function that, when called, returns blue color
objects.

(every [< 3] list) ==> tells us if 3 is smaller than each number in that
list.

(every [< _ 3] list) ==> are all numbers smaller than 3?

(mapcar [* 2] '(10 20 30)) ==> (20 40 60)

(mapcar [* $1 $1] '(1 3 5)) ==> (1 9 25)


Andr�
-- 
From: Slobodan Blazeski
Subject: Re: How to simulate currying?
Date: 
Message-ID: <13a10224-9643-47cc-9b21-8a599e45d185@41g2000yqf.googlegroups.com>
On Feb 18, 12:16 am, André Thieme <address.good.until.
···········@justmail.de> wrote:
> Slobodan Blazeski schrieb:
> > All those reader macros are great, but syntax is just discusting. Any
> > idea how to make some extended defun that will automagically create
> > curried definitions, or that will be too much work?
>
> It’s not possible.
> I wanted to implement implicit currying two years ago and found that
> it can not be done in the presence of functions that can take any number
> of args.
> If you see:  (* 3 4), should this then return 12 or
> (lambda (&rest args) (apply #'* 3 4 args)) ?
> You can not differentiate between these two cases.
No need to I would be completely satisfied with something that works
only with fixed arity functions.
>
> I wrote a macro similar to what Rob mentioned, with the $1, $2 and so
> on, but also supporting the underscore syntax.
>
> [rgb _ _ 255] returns a function that, when called, returns blue color
> objects.
>
> (every [< 3] list) ==> tells us if 3 is smaller than each number in that
> list.
>
> (every [< _ 3] list) ==> are all numbers smaller than 3?
>
> (mapcar [* 2] '(10 20 30)) ==> (20 40 60)
>
> (mapcar [* $1 $1] '(1 3 5)) ==> (1 9 25)
Nice, could you please post the code.

cheers
bobi
>
> André
> --
From: =?UTF-8?B?QW5kcsOpIFRoaWVtZQ==?=
Subject: Re: How to simulate currying?
Date: 
Message-ID: <gni22p$b4t$1@news.motzarella.org>
Slobodan Blazeski schrieb:
> On Feb 18, 12:16 am, André Thieme <address.good.until.
> ···········@justmail.de> wrote:
>> Slobodan Blazeski schrieb:
>>> All those reader macros are great, but syntax is just discusting. Any
>>> idea how to make some extended defun that will automagically create
>>> curried definitions, or that will be too much work?
>> It’s not possible.
>> I wanted to implement implicit currying two years ago and found that
>> it can not be done in the presence of functions that can take any number
>> of args.
>> If you see:  (* 3 4), should this then return 12 or
>> (lambda (&rest args) (apply #'* 3 4 args)) ?
>> You can not differentiate between these two cases.
> No need to I would be completely satisfied with something that works
> only with fixed arity functions.

That would indeed be possible, and it is not impossibly hard.
This is going to be implementation dependend code.
Two years ago when I started my cl-functional this was something I
was thinking about. Instead of defun I wanted to call it def, and allow
implicit currying in there. Later I decided to go for the [ ] which is
explicit, but so damn nice that one nearly doesn’t feel it :)
And this implicit currying could also make use of some nice features,
such as underscores and numbered args.

So, at macroexpansion time you need to find out what the signature of
your function is.
Our def macro would then walk through the body/tree, looking up each
function application and checking the arity.
The fictive function rgb for example takes 3 numbers between 0-255 and
returns a color object.
Cases:
1. (rgb)
2. (rgb 10)
3. (rgb 10 20)
4. (rgb 10 20 30)
5. (rgb _  20)
6. (rgb _  _  30)
7. (rgb $1 $1)
8. (rgb _ $1 $1)

And our def macro should replace all but one of them:

1. (lambda (a1 a2 a3) (rgb a1 a2 a3))
2. (lambda (a1 a2)    (rgb 10 a1 a2))
3. (lambda (a1)       (rgb 10 20 a1))
4.  not touched
5. (lambda (u1 a1)    (rgb u1 20 a1))
6. (lambda (u1 u2)    (rgb u1 u2 30))
7. (lambda (a1 a2)    (rgb a1 a1 a2))
8. (lambda (u1 a1)    (rgb u1 a1 a1))

This can be written nearly completely with some helper functions,
which then get called by the macro.
I started with a function that took quoted lists of code, and first
did replacements, later scanning/tree walking etc.

If we want this however outside of the def macro then the resulting code
is different.
If we imagine these 8 calls up there inside of [], then we would want:

1. (lambda (&rest args)       (apply rgb args))
2. (lambda (&rest args)       (apply rgb 10 args))
3. (lambda (&rest args)       (apply rgb 10 20 args))
4. (lambda (&rest args)       (apply rgb 10 20 30 args))
5. (lambda (u1 &rest args)    (apply rgb u1 20 args))
6. (lambda (u1 u2 &rest args) (apply rgb u1 u2 30 args))
7. (lambda (a1 &rest args)    (apply rgb a1 a1 args))
8. (lambda (u1 a1 &rest args) (apply rgb u1 a1 a1 args))


>> I wrote a macro similar to what Rob mentioned, with the $1, $2 and so
>> on, but also supporting the underscore syntax.
>>
>> [rgb _ _ 255] returns a function that, when called, returns blue color
>> objects.
>>
>> (every [< 3] list) ==> tells us if 3 is smaller than each number in that
>> list.
>>
>> (every [< _ 3] list) ==> are all numbers smaller than 3?
>>
>> (mapcar [* 2] '(10 20 30)) ==> (20 40 60)
>>
>> (mapcar [* $1 $1] '(1 3 5)) ==> (1 9 25)
> Nice, could you please post the code.

Unfortunately I can’t post it, as I have no access to it right now.
It’s in a different city. Besides that I don’t feel good with the idea
of posting my stuff. Yes, I know this sucks *g*

However, it is not extremly hard to write a few functions that work on
lists, and later reuse those functions in a def macro.

The [] currying is very powerful and goes beyond the syntactic sugar
(nothing else is currying) that other systems offer. I don’t think that
Haskells or MLs currying allows that.
Clojure for example does not offer currying, and its reader macro is
also a little chattier. Anyway, the #(..) macro comes close to [] and
offers the advantage of allowing macros.
The 8 examples in Clojure:

1. rgb
2. #(rgb 10 %&)
3. #(rgb 10 20 %)
4.  (rgb 10 20 30)
5. #(rgb % 20 %2)
6. #(rgb % %2 30)
7. #(rgb % % %2)
8. #(rgb % %2 %2)

The % is short for %1. Both have the identical effect.
The %& stands for: all args that follow
These examples are slightly longer as with the [] reader macro.
But still very acceptable.

What I also found interesting when looking into functional programming
was the idea of getting rid of Lisp-n and trying to do Lisp-1.
So, no lambda and #' anymore. When doing functional programming one
will constantly be in need of these two in a Lisp-n.
Also the idea of lazyness is pretty cool when doing functional
programming.


André
-- 
Lisp is not dead. It’s just the URL that has changed:
http://clojure.org/
From: ··················@gmail.com
Subject: Re: How to simulate currying?
Date: 
Message-ID: <242cfaac-187f-4f2d-a919-5c0c79868d23@q40g2000prh.googlegroups.com>
*delurk*

I did this:
(seemed pretty straightforward)

 (defmacro curry (fn &rest args)
   "Takes a fn, _'s and arguments (optional &rest) argument returns a
lambda "
   "Which has the _'s as variable and the arguments internalized"
  (let
    (fn-arg-list final-lambda-list rest)

    (dolist (arg args)
      (cond

	((eq arg '&rest)
	 (push '&rest final-lambda-list)
	 (setf rest (gensym))
	 (push rest final-lambda-list)
	 )

	((eq arg '_)
	 (let ((argsub (gensym)))
	   (push argsub fn-arg-list)
	   (push argsub final-lambda-list)))

	(t
	  (push arg fn-arg-list)
	  )))

    (setf fn-arg-list (reverse fn-arg-list))
    (setf final-lambda-list (reverse final-lambda-list))
    (if rest
	`(lambda ,final-lambda-list
	   (apply (function ,fn)  (nconc (list ,@fn-arg-list) ,rest)))

	`(lambda ,final-lambda-list
	   (,fn ,@fn-arg-list)))))

use with &rest:
> (apply (curry + 1 &rest) (list 1 2 3))
> 7
or as in the op
> (apply (curry + 1 _) (list 1))
> 2
or variable capture
>(let* ((a 1) (b (curry + a &rest)))
 (print (funcall b 1))
 (incf a)
 (print (funcall b 1))
 (incf a)
 (funcall b 1))

> 2
> 3
> 4

I honestly don't 'get' it... doesn't seem terribly useful unless you
are looking to win an obfuscated code contest.

(Currently adding the neat little $ syntax anyway!)

I thought this was kind of funny too:

(defmacro partial-eval (fn-args &body body)
  "Locally redefines a function
  (let
    ((fn (first fn-args))
     (args (rest fn-args))
     (rest nil)
     fn-arg-list final-lambda-list)

    (dolist (arg args)
      (cond

	((eq arg '&rest)
	 (push '&rest final-lambda-list)
	 (setf rest (gensym))
	 (push rest final-lambda-list)
	 )

	((eq arg '_)
	 (let ((argsub (gensym)))
	   (push argsub fn-arg-list)
	   (push argsub final-lambda-list)))

	(t
	  (push arg fn-arg-list)
	  )))

    (setf fn-arg-list (reverse fn-arg-list))

    (setf final-lambda-list (reverse final-lambda-list))
    (if rest
	`(flet ((,fn ,final-lambda-list
		     (apply (function ,fn)  (nconc (list ,@fn-arg-list) ,rest))))

	   ,@body)

	`(flet ((,fn ,final-lambda-list
		     (,fn ,@fn-arg-list)))
	   ,@body)
	)))

Locally redefines the function (as if curried) and does whatever is in
the body.
(example being redefine all of your +'s to add an extra one).

Could be expanded easily to do multiple bindings, might be useful for
something somewhere (?).
From: Marcus Breiing
Subject: Re: How to simulate currying?
Date: 
Message-ID: <f7b1vposw9huv@breiing.com>
* Andr� Thieme

> What I also found interesting when looking into functional
> programming was the idea of getting rid of Lisp-n and trying to do
> Lisp-1. So, no lambda and #' anymore. When doing functional
> programming one will constantly be in need of these two in a Lisp-n.

[You meant funcall, not lambda, I assume.]

Going to Lisp-1 for functional programming is throwing out the baby
with the bathwater. You don't need to inflict Lisp-1 as a cure for
FUNCALL's problem, which is that the function isn't in function
position. Just use syntax: [f x] instead of (funcall f x) means your
core algorithms in CL can look like conforming Scheme... except you
still get to use a useful macro system in a sane way:-)
From: André Thieme
Subject: Re: How to simulate currying?
Date: 
Message-ID: <gnke6a$nak$1@news.motzarella.org>
Marcus Breiing schrieb:
> * Andr� Thieme
> 
>> What I also found interesting when looking into functional
>> programming was the idea of getting rid of Lisp-n and trying to do
>> Lisp-1. So, no lambda and #' anymore. When doing functional
>> programming one will constantly be in need of these two in a Lisp-n.
> 
> [You meant funcall, not lambda, I assume.]

Good, thanks! Of course you are right.


> Going to Lisp-1 for functional programming is throwing out the baby
> with the bathwater. You don't need to inflict Lisp-1 as a cure for
> FUNCALL's problem, which is that the function isn't in function
> position. Just use syntax: [f x] instead of (funcall f x) means your
> core algorithms in CL can look like conforming Scheme... except you
> still get to use a useful macro system in a sane way:-)

Ah okay, I did not express myself well enough.
If we stay in CL then I would not want to get rid of it being a Lisp-n.
Only inside the def macro, which is a functional defun, we are in a
Lisp-1.
Even Kent Pitman agrees that Lisp-1 makes much more sense when doing
functional programming. So, one could extend the def macro in such a way
that it talks Lisp-1 with us.
But this would also mean, that this style of programming would become a
bit more �static�. Lisp needs to know at macroexpansion time what
functions exist.


(def foo (f numbers)
   (and (every (<= 0) numbers)
        (f (mapcar sqrt numbers))))


This would require Slobodan to provide a 2-ary version of < in his
functional package. Then the implicit currying could kick off.
And he can say sqrt instead of #'sqrt or (function sqrt).
Also we can say (f ...) instead of (funcall f ...).
For doing this the def macro would have to look up f in the list of
all functions that exist. If it is not in there, then def automatically
adds a funcall in front of f.
If we defun f afterwards then foo needs a recompile, and f would have
to be renamed in the argument list. (and be declared to be ignored, as
it is not used anymore).


Andr�
-- 
Lisp is not dead. It�s just the URL that has changed:
http://clojure.org/
From: Pascal Costanza
Subject: Re: How to simulate currying?
Date: 
Message-ID: <6vp4nbFl8ireU1@mid.individual.net>
Slobodan Blazeski wrote:
> I want to make bind symbol _ to represent omitteed parameter so I
> could make automatical currying using CLOS, all methods are of fixed
> arity. So far I did this:
> 
> (defclass blank () ())
> (defconstant _ (make-instance 'blank))
> 
> (defmethod plus ((x blank) (y number))
>    (lambda (n) (+ n y)))
> 
> (defmethod plus ((x number) (y blank))
>    (lambda (n) (+ x n)))
> 
> (funcall (plus 2 _) 3)
> 5
> 
> Though it works is there is some more elegant way? Preferably without
> making class for one lousy symbol.

Try eql specializers:

(defmethod plus ((x (eql '_)) (y number)
   ...)

etc.


Pascal

-- 
ELS'09: http://www.european-lisp-symposium.org/
My website: http://p-cos.net
Common Lisp Document Repository: http://cdr.eurolisp.org
Closer to MOP & ContextL: http://common-lisp.net/project/closer/
From: Slobodan Blazeski
Subject: Re: How to simulate currying?
Date: 
Message-ID: <b219abd7-57cc-4a93-873f-94f5888e94bc@w34g2000yqm.googlegroups.com>
On Feb 15, 1:08 am, Pascal Costanza <····@p-cos.net> wrote:
> Slobodan Blazeski wrote:
> > I want to make bind symbol _ to represent omitteed parameter so I
> > could make automatical currying using CLOS, all methods are of fixed
> > arity. So far I did this:
>
> > (defclass blank () ())
> > (defconstant _ (make-instance 'blank))
>
> > (defmethod plus ((x blank) (y number))
> >    (lambda (n) (+ n y)))
>
> > (defmethod plus ((x number) (y blank))
> >    (lambda (n) (+ x n)))
>
> > (funcall (plus 2 _) 3)
> > 5
>
> > Though it works is there is some more elegant way? Preferably without
> > making class for one lousy symbol.
>
> Try eql specializers:
>
> (defmethod plus ((x (eql '_)) (y number)
>    ...)

Just what I needed. Many thanks.

cheers
bobi
>
> etc.
>
> Pascal
>
> --
> ELS'09:http://www.european-lisp-symposium.org/
> My website:http://p-cos.net
> Common Lisp Document Repository:http://cdr.eurolisp.org
> Closer to MOP & ContextL:http://common-lisp.net/project/closer/
From: Pascal J. Bourguignon
Subject: Re: How to simulate currying?
Date: 
Message-ID: <87tz6wmu28.fsf@galatea.local>
Slobodan Blazeski <·················@gmail.com> writes:

> I want to make bind symbol _ to represent omitteed parameter so I
> could make automatical currying using CLOS, all methods are of fixed
> arity. So far I did this:
>
> (defclass blank () ())
> (defconstant _ (make-instance 'blank))
>
> (defmethod plus ((x blank) (y number))
>    (lambda (n) (+ n y)))
>
> (defmethod plus ((x number) (y blank))
>    (lambda (n) (+ x n)))
>
> (funcall (plus 2 _) 3)
> 5
>
> Though it works is there is some more elegant way? Preferably without
> making class for one lousy symbol.

(defconstant _ '_)
(defmethod plus ((x (eql _)) (y number)) (lambda (n) (+ n y)))
(defmethod plus ((y number) (x (eql _))) (lambda (n) (+ n y)))
(funcall (plus 2 _) 3)

-- 
__Pascal Bourguignon__
From: John Thingstad
Subject: Re: How to simulate currying?
Date: 
Message-ID: <op.upde2pexut4oq5@pandora.alfanett.no>
P� Sun, 15 Feb 2009 00:29:41 +0100, skrev Slobodan Blazeski  
<·················@gmail.com>:

> I want to make bind symbol _ to represent omitteed parameter so I
> could make automatical currying using CLOS, all methods are of fixed
> arity. So far I did this:
>
> (defclass blank () ())
> (defconstant _ (make-instance 'blank))
>
> (defmethod plus ((x blank) (y number))
>    (lambda (n) (+ n y)))
>
> (defmethod plus ((x number) (y blank))
>    (lambda (n) (+ x n)))
>
> (funcall (plus 2 _) 3)
> 5
>
> Though it works is there is some more elegant way? Preferably without
> making class for one lousy symbol.
>
> cheers
> bobi

Hmm.. Are you aware that this creates a combinatorical explosion on the  
number of arguments? Works fine as long all your methods are binary I  
suppose..

--------------
John Thingstad
From: Slobodan Blazeski
Subject: Re: How to simulate currying?
Date: 
Message-ID: <d1765da8-d08e-418f-84f0-37a38a3ece96@b16g2000yqb.googlegroups.com>
On Feb 15, 3:12 am, "John Thingstad" <·······@online.no> wrote:
> På Sun, 15 Feb 2009 00:29:41 +0100, skrev Slobodan Blazeski  
> <·················@gmail.com>:
>
>
>
>
>
> > I want to make bind symbol _ to represent omitteed parameter so I
> > could make automatical currying using CLOS, all methods are of fixed
> > arity. So far I did this:
>
> > (defclass blank () ())
> > (defconstant _ (make-instance 'blank))
>
> > (defmethod plus ((x blank) (y number))
> >    (lambda (n) (+ n y)))
>
> > (defmethod plus ((x number) (y blank))
> >    (lambda (n) (+ x n)))
>
> > (funcall (plus 2 _) 3)
> > 5
>
> > Though it works is there is some more elegant way? Preferably without
> > making class for one lousy symbol.
>
> > cheers
> > bobi
>
> Hmm.. Are you aware that this creates a combinatorical explosion on the  
> number of arguments? Works fine as long all your methods are binary I  
> suppose..
Yeah, I won't need it for nothing more than dyads.

cheers
bobi


>
> --------------
> John Thingstad
From: ·········@att.net
Subject: Re: How to simulate currying?
Date: 
Message-ID: <4f24aea7-5596-445c-8b96-c54cfd4dd196@f24g2000vbf.googlegroups.com>
On Feb 14, 5:29 pm, Slobodan Blazeski <·················@gmail.com>
wrote:
> I want to make bind symbol _ to represent omitteed parameter so I
> could make automatical currying using CLOS
> Though it works is there is some more elegant way?

Here's a reader macro that handles arbitrary numbers and locations of
specified and unspecified arguments:

(defun |read-#func| (stream char n)
  (declare (ignore char))
  (let (vars outforms (informs (read stream t :eof t)))
    (flet ((pushvar ()
             (let ((var (gensym)))
               (push var vars)
               (push var outforms))))
      (dolist (x informs)
        (if (and (symbolp x) (string= (symbol-name x) "_"))
            (pushvar)
            (push x outforms)))
      (dotimes (_ (or n 0))
        (pushvar)))
    `(lambda ,(nreverse vars) ,(nreverse outforms))))

(set-dispatch-macro-character #\# #\f #'|read-#func|)


(funcall #f(+ 2 _) 3) => 5

--Dan
From: Kaz Kylheku
Subject: Re: How to simulate currying?
Date: 
Message-ID: <20090222185300.560@gmail.com>
On 2009-02-15, ·········@att.net <·········@att.net> wrote:
> (funcall #f(+ 2 _) 3) => 5

This has little notational advantage over a regular macro:

  (fn + 2 _)

I.e. a kind of lambda syntax where instead of naming the parameters in a lambda
list, you scatter them throughout a body where they are picked out by being
lexically distinct. You might as well support numbered ones, like _1, _2, ...
Then _ acts like the highest-numbered one, if mixed with the numbered ones.
From: ·········@att.net
Subject: Re: How to simulate currying?
Date: 
Message-ID: <5d844234-743b-4045-94eb-9556564a9aaf@q18g2000vbn.googlegroups.com>
> On 2009-02-15, ·········@att.net <·········@att.net> wrote:
> > (funcall #f(+ 2 _) 3) => 5

On Feb 16, 12:39 am, Kaz Kylheku <········@gmail.com> wrote:
> This has little notational advantage over a regular macro:
>   (fn + 2 _)

One advantage of using a reader macro is that it expands to a regular
lambda form before any other regular macros see it.  A regular macro
would introduce a new symbol.  It's also convenient to be able to
write things like #3f(foo bar) for #f(foo bar _ _ _).

> You might as well support numbered ones, like _1, _2, ...
> Then _ acts like the highest-numbered one, if mixed with the numbered ones.

That's an interesting thought.  I would use dollar signs for numbered
arguments, and I would keep them as a separate alternate syntax.  I
would first scan the form for an underline, and ignore all other
arguments if one or more is found.  If there's no _, then I would scan
for numbered arguments $1, $2, etc..
From: Chris Riesbeck
Subject: Re: How to simulate currying?
Date: 
Message-ID: <6vttr4FlmplnU1@mid.individual.net>
·········@att.net wrote:
>> On 2009-02-15, ·········@att.net <·········@att.net> wrote:
>>> (funcall #f(+ 2 _) 3) => 5
> 
> On Feb 16, 12:39 am, Kaz Kylheku <········@gmail.com> wrote:
>> This has little notational advantage over a regular macro:
>>   (fn + 2 _)
> 
> One advantage of using a reader macro is that it expands to a regular
> lambda form before any other regular macros see it. 

?? I'm not sure what the issue is here. Code-crawling macros have to be 
smart enough to macroexpand what they call, any other macros shouldn't 
notice the difference.

> A regular macro
> would introduce a new symbol. 

Vs introducing new reader syntax. Not sure why one is better than the 
other. In my normal hierarchy of hackery, I use macros only when regular 
functions won't do, and new reader syntax only when macros won't do.

> It's also convenient to be able to
> write things like #3f(foo bar) for #f(foo bar _ _ _).

Does that actually come up much?
From: ·········@att.net
Subject: Re: How to simulate currying?
Date: 
Message-ID: <473f4ca6-ddf6-4e06-b1e4-ba98d2bdd2d4@r29g2000vbp.googlegroups.com>
> ·········@att.net wrote:
> > One advantage of using a reader macro is that it expands to a regular
> > lambda form before any other regular macros see it.

On Feb 16, 1:41 pm, Chris Riesbeck <··············@gmail.com> wrote:
> ?? I'm not sure what the issue is here.

Sorry, I forgot about my 2-fix syntax.  Maybe you're right.  I also
use another reader macro that implements a sort of quasi-infix syntax
with square brackets.  It swaps the CAR and the CADR of the form.  So
#f[_ > n] would expand to (lambda (#G1) (> #G1 n)).

> > It's also convenient to be able to
> > write things like #3f(foo bar) for #f(foo bar _ _ _).
> Does that actually come up much?

I'm not sure.  I included that code because it's easy to write and
harmless to use, and I would expect it to be helpful once in a while.
It makes the syntax about as compact as partial application in ML.

--Dan
From: Chris Riesbeck
Subject: Re: How to simulate currying?
Date: 
Message-ID: <7007msFm6ojeU1@mid.individual.net>
·········@att.net wrote:
>> On 2009-02-15, ·········@att.net <·········@att.net> wrote:
>>> (funcall #f(+ 2 _) 3) => 5
> 
> On Feb 16, 12:39 am, Kaz Kylheku <········@gmail.com> wrote:
>> This has little notational advantage over a regular macro:
>>   (fn + 2 _)
> 
> One advantage of using a reader macro is that it expands to a regular
> lambda form before any other regular macros see it.  A regular macro
> would introduce a new symbol.  It's also convenient to be able to
> write things like #3f(foo bar) for #f(foo bar _ _ _).
> 
>> You might as well support numbered ones, like _1, _2, ...
>> Then _ acts like the highest-numbered one, if mixed with the numbered ones.
> 
> That's an interesting thought.  I would use dollar signs for numbered
> arguments, and I would keep them as a separate alternate syntax.  I
> would first scan the form for an underline, and ignore all other
> arguments if one or more is found.  If there's no _, then I would scan
> for numbered arguments $1, $2, etc.. 

For contrast, here's a straight macro version. Every _ is replaced by a 
gensym, every _n is replaced by a previous _ variable (one-based). Any 
other use of _xxx is left alone.

 > (mapcar (_ (max _ _)) '(3 5 7) '(1 6 5))
(3 6 7)

 > (remove-if (_ (numberp (car _))) '((a 1) (2 b) (3 c) (d 4)))
((A 1) (D 4))

 > (mapcan (_ (and (> _ _) (list _1))) '(3 5 7) '(1 6 5))
(3 7)

I was less interested in the macro than reducing the loop code to build 
the form and collect the gensymed variables. The actual loop is just 
half of this code. The rest is devoted to handling _ vs _n vs other _ 
variables.

(defmacro _ (&rest l)
   (debar nil l
          (lambda (vars exps)
            `(lambda ,(nreverse vars) ,@exps))))

(defun debar (vars form fn)
   (or (bar-replace vars form fn)
       (if (consp form)
           (debar vars (car form)
             (lambda (vars car-form)
               (debar vars (cdr form)
                  (lambda (vars cdr-form)
                    (funcall fn vars
                             (cons car-form cdr-form)))))))
       (funcall fn vars form)))

;; the _ symbol handler

(defun bar-replace (vars form fn)
   (let ((n (get-var-index form)))
     (cond ((not (numberp n)) nil)
           ((zerop n)
            (let ((var (gensym)))
              (funcall fn (cons var vars) var)))
           ((plusp n)
            (funcall fn vars (nth (- (length vars) n) vars)))
           (t nil))))

(defun get-var-index (form)
   (and (symbolp form)
        (let ((name (symbol-name form)))
          (and (eql (char name 0) #\_)
               (if (= (length name) 1) 0
                 (parse-integer name :start 1 :junk-allowed t))))))
From: Marco Antoniotti
Subject: Re: How to simulate currying?
Date: 
Message-ID: <bf5bce4f-fe05-462a-84cb-ee60f2116f50@k19g2000yqg.googlegroups.com>
On Feb 17, 5:42 pm, Chris Riesbeck <··············@gmail.com> wrote:
> ·········@att.net wrote:
> >> On 2009-02-15, ·········@att.net <·········@att.net> wrote:
> >>> (funcall #f(+ 2 _) 3) => 5
>
> > On Feb 16, 12:39 am, Kaz Kylheku <········@gmail.com> wrote:
> >> This has little notational advantage over a regular macro:
> >>   (fn + 2 _)
>
> > One advantage of using a reader macro is that it expands to a regular
> > lambda form before any other regular macros see it.  A regular macro
> > would introduce a new symbol.  It's also convenient to be able to
> > write things like #3f(foo bar) for #f(foo bar _ _ _).
>
> >> You might as well support numbered ones, like _1, _2, ...
> >> Then _ acts like the highest-numbered one, if mixed with the numbered ones.
>
> > That's an interesting thought.  I would use dollar signs for numbered
> > arguments, and I would keep them as a separate alternate syntax.  I
> > would first scan the form for an underline, and ignore all other
> > arguments if one or more is found.  If there's no _, then I would scan
> > for numbered arguments $1, $2, etc..
>
> For contrast, here's a straight macro version. Every _ is replaced by a
> gensym, every _n is replaced by a previous _ variable (one-based). Any
> other use of _xxx is left alone.
>
>  > (mapcar (_ (max _ _)) '(3 5 7) '(1 6 5))
> (3 6 7)
>
>  > (remove-if (_ (numberp (car _))) '((a 1) (2 b) (3 c) (d 4)))
> ((A 1) (D 4))
>
>  > (mapcan (_ (and (> _ _) (list _1))) '(3 5 7) '(1 6 5))
> (3 7)
>
> I was less interested in the macro than reducing the loop code to build
> the form and collect the gensymed variables. The actual loop is just
> half of this code. The rest is devoted to handling _ vs _n vs other _
> variables.
>
> (defmacro _ (&rest l)
>    (debar nil l
>           (lambda (vars exps)
>             `(lambda ,(nreverse vars) ,@exps))))
>
> (defun debar (vars form fn)
>    (or (bar-replace vars form fn)
>        (if (consp form)
>            (debar vars (car form)
>              (lambda (vars car-form)
>                (debar vars (cdr form)
>                   (lambda (vars cdr-form)
>                     (funcall fn vars
>                              (cons car-form cdr-form)))))))
>        (funcall fn vars form)))
>
> ;; the _ symbol handler
>
> (defun bar-replace (vars form fn)
>    (let ((n (get-var-index form)))
>      (cond ((not (numberp n)) nil)
>            ((zerop n)
>             (let ((var (gensym)))
>               (funcall fn (cons var vars) var)))
>            ((plusp n)
>             (funcall fn vars (nth (- (length vars) n) vars)))
>            (t nil))))
>
> (defun get-var-index (form)
>    (and (symbolp form)
>         (let ((name (symbol-name form)))
>           (and (eql (char name 0) #\_)
>                (if (= (length name) 1) 0
>                  (parse-integer name :start 1 :junk-allowed t))))))

Very cool.  Why not call the macro /_ (looks like a big L)?  :)

Cheers
--
Marco
From: Chris Riesbeck
Subject: Re: How to simulate currying?
Date: 
Message-ID: <700qdaFma9maU1@mid.individual.net>
Marco Antoniotti wrote:
> On Feb 17, 5:42 pm, Chris Riesbeck <··············@gmail.com> wrote:

>> For contrast, here's a straight macro version. Every _ is replaced by a
>> gensym, every _n is replaced by a previous _ variable (one-based). Any
>> other use of _xxx is left alone.
> 
> Very cool.  Why not call the macro /_ (looks like a big L)?  :)
> 
> Cheers
> --
> Marco

As I recall, Drew McDermott had a lambda macro \   -- that's backslash 
space.
From: Rob Warnock
Subject: Re: How to simulate currying?
Date: 
Message-ID: <jfKdnR57IdW_AQbUnZ2dnUVZ_oWdnZ2d@speakeasy.net>
Chris Riesbeck  <··············@gmail.com> wrote:
+---------------
| ·········@att.net wrote:
| > Kaz Kylheku <········@gmail.com> wrote:
| >> You might as well support numbered ones, like _1, _2, ...
| >> Then _ acts like the highest-numbered one, if mixed with the numbered ones.
| > 
| > That's an interesting thought.  I would use dollar signs for numbered
| > arguments, and I would keep them as a separate alternate syntax.  I
| > would first scan the form for an underline, and ignore all other
| > arguments if one or more is found.  If there's no _, then I would scan
| > for numbered arguments $1, $2, etc.. 
| 
| For contrast, here's a straight macro version. Every _ is replaced by a 
| gensym, every _n is replaced by a previous _ variable (one-based). Any 
| other use of _xxx is left alone.
...
|  > (mapcan (_ (and (> _ _) (list _1))) '(3 5 7) '(1 6 5))
| (3 7)
+---------------

I understand that you can back-reference already used "_"s, but
how do you specify order *without* backreference. E.g., how do you
do the same as the following in my "#$" readmacro:

    > (mapcar #$(list $2 $1) '(3 5 7) '(1 6 5))

    ((1 3) (6 5) (5 7))
    > 

The only way I could figure out how to do it with your syntax was
to create "do nothing" uses of "_" to anchor the back-references to:

    > (mapcar (_ _ _ (list _2 _1)) '(3 5 7) '(1 6 5))

    ((1 3) (6 5) (5 7))
    > 

Am I missing something obvious?


-Rob

p.s. Thanks for the reminder that a one- or two-character plain ol'
macro is quite sufficient for this sort of LAMBDA abbreviation stuff.
Readmacros really *aren't* needed here!

I already have a FN macro which is a simple abbrevation
for LAMBDA. If I add scanning for "$n" variables, it would
enable *both* styles:

    (fn (x y) (list y x) ; still useful when nesting, to avoid arg capture
or:
    (fn (list $2 $1))    ; implicit arglist

All that "#$" would buy then is one fewer set of parens and a space:

    #$(list $2 $1)

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Chris Riesbeck
Subject: Re: How to simulate currying?
Date: 
Message-ID: <70333aFmf4hsU1@mid.individual.net>
Rob Warnock wrote:
> Chris Riesbeck  <··············@gmail.com> wrote:
> | 
> | For contrast, here's a straight macro version. Every _ is replaced by a 
> | gensym, every _n is replaced by a previous _ variable (one-based). Any 
> | other use of _xxx is left alone.
> ...
> |  > (mapcan (_ (and (> _ _) (list _1))) '(3 5 7) '(1 6 5))
> | (3 7)
> +---------------
> 
> I understand that you can back-reference already used "_"s, but
> how do you specify order *without* backreference. E.g., how do you
> do the same as the following in my "#$" readmacro:
> 
>     > (mapcar #$(list $2 $1) '(3 5 7) '(1 6 5))
> 
>     ((1 3) (6 5) (5 7))

I had a different semantics in my head. How do non-indexed forms fit in 
with indexed ones, e.g., what's the lambda equivalent for

    $(list $3 $ $1)
From: Rob Warnock
Subject: Re: How to simulate currying?
Date: 
Message-ID: <T9adnbGnRt2gyQDUnZ2dnUVZ_rfinZ2d@speakeasy.net>
Chris Riesbeck  <··············@gmail.com> wrote:
+---------------
| Rob Warnock wrote:
| > Chris Riesbeck  <··············@gmail.com> wrote:
| > | For contrast, here's a straight macro version. Every _ is replaced by a 
| > | gensym, every _n is replaced by a previous _ variable (one-based). Any 
| > | other use of _xxx is left alone.
| > ...
| > |  > (mapcan (_ (and (> _ _) (list _1))) '(3 5 7) '(1 6 5))
| > | (3 7)
| > +---------------
| > 
| > I understand that you can back-reference already used "_"s, but
| > how do you specify order *without* backreference. E.g., how do you
| > do the same as the following in my "#$" readmacro:
| > 
| >     > (mapcar #$(list $2 $1) '(3 5 7) '(1 6 5))
| > 
| >     ((1 3) (6 5) (5 7))
| 
| I had a different semantics in my head. How do non-indexed forms fit in 
| with indexed ones, e.g., what's the lambda equivalent for
| 
|     $(list $3 $ $1)
+---------------

I don't know what you mean by that form. But if you meant
#$(list $3 $ $1), well, my current "#$" readmacro doesn't do
anything special with a naked "$" [unlike your macro with "_"],
so it's simply this:

    > (read-from-string "#$(list $3 $ $1)")

      (LAMBDA (&OPTIONAL $1 $2 $3 $4 $5 $6 $7 $8 $9 &REST $*)
	(DECLARE (IGNORABLE $1 $2 $3 $4 $5 $6 $7 $8 $9 $*))
	(LIST $3 $ $1))
      16
    >

and "$" is a free variable.

If you really meant to type #$(list $3 $* $1), then in the improved
version of "#$" I was discussing before [where the &REST parameter
"$*" occurs just after the highest "${n}" seen], the expansion would be:

      (LAMBDA ($1 $2 $3 &REST $*)
	(DECLARE (IGNORE $2))
	(LIST $3 $* $1))

But to ask my question again, with your "_" macro, how do you
(or can you) re-order arguments without providing dummy occurrences
of "_" to provide anchors for back-references? That is, you can write a
(PAIRLIS LIST1 LIST2) in my "#$" as (MAPCAR #$(CONS $1 $2) LIST1 LIST2)
and in your "_" macro as (MAPCAR (_ (CONS _ _)) LIST1 LIST2) -- no problem
there.

And one can write a [hypothetical] (SWAPPED-PAIRLIS LIST1 LIST2) in "#$" as
(MAPCAR #$(CONS $2 $1) LIST1 LIST2), but in your "_" the only way I could
figure out how to write it was (MAPCAR (_ _ _ (CONS _2 _1)) LIST1 LIST2).
Is there a simpler way? One that leaves   \_\___ these out?


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Tobias C. Rittweiler
Subject: Re: How to simulate currying?
Date: 
Message-ID: <87ocwyy3wo.fsf@freebits.de>
Chris Riesbeck <...> writes:

> For contrast, here's a straight macro version. Every _ is replaced by
> a gensym, every _n is replaced by a previous _ variable
> (one-based). Any other use of _xxx is left alone.

As a side note, notice that tokens like _1, &c fall under
implementation-dependent realms as they're potential numbers. 

See CLHS 2.3.1.1.

  -T.
From: Rob Warnock
Subject: Re: How to simulate currying?
Date: 
Message-ID: <jbmdnSsqUK0BoAPUnZ2dnUVZ_qrinZ2d@speakeasy.net>
Tobias C. Rittweiler <···@freebits.de.invalid> wrote:
+---------------
| Chris Riesbeck <...> writes:
| > For contrast, here's a straight macro version. Every _ is replaced by
| > a gensym, every _n is replaced by a previous _ variable
| > (one-based). Any other use of _xxx is left alone.
| 
| As a side note, notice that tokens like _1, &c fall under
| implementation-dependent realms as they're potential numbers. 
| See CLHS 2.3.1.1.
+---------------

Thanks for reminding us of that obscure little tidbit!  ;-}

By the way, is the term "extension character" defined *anywhere*
in the CLHS other than parenthetically in passing on page 2.3.1.1?!?
[A massive "grep" suggests it is not. It's certainly not in the
Glossary!!] And is it *ever* any other character besides caret (^)
or underscore (_)?

Also, note that CLHS 2.3.1.1.2 permits -- but does not require --
a conforming implementation to define the meaning of tokens that
are potential numbers but actually numbers. CMUCL, for one example,
defines them as symbols, but always prints them using the multiple-
escape syntax [just so you know you're being naughty? ;-} ], e.g.:

    cmu> (defun foo (x)          
	   (let ((v (read-from-string x)))
	     (format t "~s is a ~a~%" v (type-of v))
	     (values)))

    FOO
    cmu> (foo "1b5000")   ; Note the multiple escapes.
    |1B5000| is a SYMBOL
    cmu> (foo "777777q")  ; Ditto.
    |777777Q| is a SYMBOL
    cmu> (foo "777$")     ; None here, since $ is not an extension character.
    777$ is a SYMBOL
    cmu> (foo "$1")       ; Nor here.
    $1 is a SYMBOL
    cmu> (foo "_1")       ; Oops.
    |_1| is a SYMBOL
    cmu> 

So the "_1" tokens will work [but may print funny!] in any
implementation which makes symbols of potential numbers,
but in any case they're not completely portable.

Hmmm... Assessing the risk...

Does anyone know of an implementation that *does* implement
some sort of "extended numbers" using "^" and/or "_"? 

And does anyone know of an implementation that *doesn't* treat
potential numbers that aren't actually numbers as symbols?


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Tobias C. Rittweiler
Subject: Re: How to simulate currying?
Date: 
Message-ID: <87vdr5jy81.fsf@freebits.de>
Rob Warnock writes:

> Does anyone know of an implementation that *does* implement
> some sort of "extended numbers" using "^" and/or "_"? 
>
> And does anyone know of an implementation that *doesn't* treat
> potential numbers that aren't actually numbers as symbols?

ZetaLisp did use them; quoting the Chinual:

  Traditional syntax also permits a simple integer, followed by an
  underscore (_) or a circumflex (^), followed by another simple
  integer. The two simple integers are interpreted in the usual way; the
  character in between indicates an operation that is then performed on
  the two integers. The underscore indicates a binary ``left shift'';
  that is, the integer to its left is doubled the number of times
  indicated by the integer to its right. The circumflex multiplies the
  integer to its left by *read-base* the number of times indicated by
  the integer to its right. (The second simple integer is not allowed to
  have a leading minus sign.) Examples: 3_2 means 12 and 645^3 means
  645000.

    -T.
From: Rob Warnock
Subject: Re: How to simulate currying?
Date: 
Message-ID: <WdSdnZ0gI5PrLAPUnZ2dnUVZ_uidnZ2d@speakeasy.net>
Tobias C. Rittweiler <···@freebits.de> wrote:
+---------------
| Rob Warnock writes:
| > Does anyone know of an implementation that *does* implement
| > some sort of "extended numbers" using "^" and/or "_"? 
| >
| > And does anyone know of an implementation that *doesn't* treat
| > potential numbers that aren't actually numbers as symbols?
| 
| ZetaLisp did use them...
+---------------

Thanks!


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Vsevolod
Subject: Re: How to simulate currying?
Date: 
Message-ID: <6e7224a5-b4d9-4827-9971-c370c2d2a2ab@t13g2000yqc.googlegroups.com>
On Feb 16, 8:39 am, Kaz Kylheku <········@gmail.com> wrote:
> On 2009-02-15, ·········@att.net <·········@att.net> wrote:
>
> > (funcall #f(+ 2 _) 3) => 5
>
> This has little notational advantage over a regular macro:
>
>   (fn + 2 _)
>
> I.e. a kind of lambda syntax where instead of naming the parameters in a lambda
> list, you scatter them throughout a body where they are picked out by being
> lexically distinct. You might as well support numbered ones, like _1, _2, ...
> Then _ acts like the highest-numbered one, if mixed with the numbered ones.

Another advantage of a reader-macro in this case is that, since it
expands into a lambda form, it can be used in the car position of a
list:
CL-USER> ((lambda (a b) (+ a b)) 2 2)
4
CL-USER> (#`(+ 2 _) 2)
4
CL-USER> ([+ $2 $2] 2 2)
4
From: eric-and-jane-smith
Subject: Re: How to simulate currying?
Date: 
Message-ID: <Alpol.35609$xQ5.3887@newsfe23.iad>
This is about function composition and only incidentally about currying.  
I wrote this macro because in another thread I saw someone use something 
like (compose #'not #'null) to convert non-nil to T.  From my point of 
view the whole purpose of using such stuff is to make the code neater and 
shorter to make it easier to read.  So instead of (compose #'not #'null) 
I would rather use something like (cf not not) which is the purpose of 
this macro.  I also added a bunch of other features to it, all intended 
to make the code shorter and more readable.  E.g. (cf (* 10)) makes a 
function to multiply its argument by 10, which seems to me neater and 
more readable than (lambda (x) (* x 10)).


; cf = Compose function with optional currying.
; Example usage:
; (mapcar (cf (* 2) (+ 10 20) -) '(1 2 3))
; ==> (-32 -34 -36)
; Each argument to cf gets converted to a function,
; and the functions are applied in left to right
; order.  E.g. (cf f1 f2 f3) is equivalent to
; (lambda (x) (f3 (f2 (f1 x))))
; Arguments accepted by cf:
; * #'name and 'name have their usual meanings.
;   I.e. #'name names a function in lexical scope
;   but 'name is only global.
; * name (unquoted) is #'name with #' elided.  Note
;   this contradicts the normal Lisp convention.
; * ''form has the same meaning form unquoted would
;   have in the normal Lisp convention.  E.g. to
;   get the function from a variable as in
;   (funcall var) use ''var instead of just var.
; * (/x a b c) is shorthand for (lambda (x) a b c)
;   But there is no /y or anything, just /x.
; * (func 1 2 3) is to curry.  I.e. it gets
;   converted to (lambda (x) (func x 1 2 3))
; * Special case:  If one of the curry args is a $
;   then the non-curried arg takes the place of the
;   $ instead of being leftmost.
;   (func 1 2 $)  =  (lambda (x) (func 1 2 x))
;   E.g.  (cf (+ 1) (/ 1 $))  =  1/(x+1)
(defmacro cf (&rest xs)
  (loop with argname = (gensym)
        as x in (cons nil xs)
        as curryargs = nil
        as func = (if (atom x)
                      `#',x
                    (case (car x)
                      (quote       (if (and (consp (cadr x))
                                            (eq (caadr x) 'quote))
                                       (cadadr x)
                                     x))
                      (function    x)
                      (/x          `(lambda (x) ,@(cdr x)))
                      (t           (setq curryargs (cdr x))
                                   `#',(car x))))
        as args = (if (member '$ curryargs)
                      (loop as x in curryargs collect
                        (if (eq x '$) argname x))
                    (nconc (list code) curryargs))
        as code = argname then `(funcall ,func ,@args)
        finally (return `(lambda (,argname) ,code))))