From: Chris Paris
Subject: Why lisp is not my favorite programming language
Date: 
Message-ID: <C3DHJL.Dun.2@cs.cmu.edu>
I've been programming in SML and (more recently) Haskell as a hobby.
I'm very excited about how natural and fun it is to program in these
languages, and I plan to use one or the other (probably Haskell) for
any project I do on my own. Recently I've started programming in lisp
because I'm helping a friend who's taking a class that requires the
assignments to be done in lisp. I'm finding the experience of
programming in lisp to be most unpleasant. You read that people
learning lisp often have the problem of "programming Pascal in lisp,"
and that this is bad. Perhaps you can generalize this, because we're
"programming Haskell in lisp." Almost literally, in fact, because we
first write the programs in Haskell (really Gofer) and then translate
them to lisp. Writing in Haskell lets us worry just about the
mathematical characteristics of the problem to solve, without having
to worry about how to express the ideas in a particular language (the
language part is easy).

Once we have a clear and correct program in Haskell, it's time
to convert it to lisp, and Oh My Gawd, we run into the following
problems that make us write lisp code that's much much harder to
understand than the equivalent Haskell code.

1. no pattern matching (destructuring-bind isn't real pattern matching)
2. no (transparent) support for curried function application
3. magic difference between functions and symbols that are bound to
   lambda abstractions. I.e., you have to funcall the latter and not
   the former.
4. (most annoying of all) can't define local functions and local
   variables at the same level. You have to nest flet/labels and
   let/let*.

What surprises me is how fond of lisp many people are despite these
characteristics which I find so unpleasant. Considering this, I'm
sincerely hoping that some lisp experts will enlighten me on the lisp
way of thinking about my four points.

What comforts me is that most of the things I wish lisp supported are
just syntactic sugar. It would be possible to write macros to
implement all of the things in my list. I've written a first cut at
some macros to solve problems 2, 3, and 4. I'd like to know if anyone
has written a macro package to do anything on my list, or in general,
to make lisp more friendly.

Chris Paris
····@cmu.edu

From: Joshua M Yelon
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <C3Ds4G.EKJ@news.cso.uiuc.edu>
The three things you requested (not in this order) were:

  1. You would like a function-definition construct that allows you to
     specify several possible bodies, and pattern templates that select
     a body at runtime based on the values of the actual parameters.

  2. You would like the language to curry function-calls automatically.

  3. You would like a single name space for both functions and other values.

I believe that #1 would be neat.  I personally don't think that #2 and #3
are a good ideas, but hey - that's a subjective judgement, based on my
own somewhat biased preferences.

As a little excercise, I implemented #2 and #3, to see if they could be done.
Here they are, in 24 lines of code for both.  I didn't bother with #1 - it's
harder, but very straighforward to implement.

Happy hacking!  - Josh

------------------------------ CUT HERE -------------------------------------
;
; This is 'ONS' - the "One Name Space" module.
;
; Some programming languages (ie, scheme) assume a single name space for
; both named functions and other named values.  Lisp has two name spaces: 
; names can have both function-bindings and value-bindings.  For
; the convenience of those attempting to translate scheme-like languages
; into lisp, this module attempts to bypass (ignore) the function-bindings
; and use value-bindings for everything.
;
; Here's how it works --- the user of this module writes code that looks
; like this:
;
;   [if [> x y]
;     [print x]
;     [print y]]
;
; and the bracket readmacro converts it into this:
;
;   (if (funcall > x y)
;     (funcall print x)
;     (funcall print y))
;
; in other words, it sticks the word 'funcall' in front of every named
; function application (it doesn't modify special forms or macro
; calls). This causes the code to consistently use value-bindings, not
; function-bindings, for everything.
;
; If the user sticks consistently to the bracket syntax, he will never
; reference a function-binding.  He should also never create a function
; binding - ie, he should consistently use LET instead of FLET to define
; local named functions, and he should use setf-symbol-value (or
; some equivalent sugared form) to create top-level named functions.
;
; Remember: lists of bindings, lambda lists, lambda expressions,
; etcetera are NOT executable forms: they should be left in parentheses.
;
;    EXAMPLE:
;
;   [let ((x 1)
;         (f #'(lambda (y) (+ y 2))))
;       [print [f x]]]
;
; As a convenience, this module also copies all the already-extant
; symbol-functions into their respective symbol-values.
;
; And, naturally, I don't really recommend _using_ this silly
; thing.  The double name-space is usually exactly what you want, and
; funcall isn't too hard to type.
;

(defun ons-right-bracket-readmacro (s chr)
    (error "Right bracket occurred without left bracket"))

(defun ons-left-bracket-readmacro (s chr &aux res)
    (declare (ignore chr))
        (let ((list (read-delimited-list #\] s t)))
            (if (or (special-form-p (car list))(macro-function (car list)))
                list
                (cons 'funcall list))))

(set-macro-character #\[ #'ons-left-bracket-readmacro)
(set-macro-character #\] #'ons-right-bracket-readmacro)

(do-all-symbols (x)
    (if (fboundp x)
        (setf (symbol-value x) (symbol-function x))))


;
; This is SELF-CURRYING-LAMBDA, a construct for defining lambda-functions
; that return curried versions of themselves if you apply them to too few
; arguments.  Use this:
;
; (setf adder (self-currying-lambda (x y) (+ x y)))
;
; instead of this:
;
; (setf adder (function (lambda (x y) (+ x y))))
;
; and your adder will curry itself on application to one argument.
;

(defmacro SELF-CURRYING-LAMBDA ((&rest formals) &rest body)
   `(let ((args-needed (length ',formals)))
        (labels ((self-currying (&rest args)
                    (if (eql (length args) args-needed)
                         (funcall #'(lambda ,formals ,@body) args)
                       #'(lambda (&rest more-args)
                            (self-currying (append args more-args))))))
            #'self-currying)))
From: [Invalid-From-Line]
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <1993Mar04.194522.1110@ncrcae.ColumbiaSC.NCR.COM>
You don't like Lisp as well as Haskell because it's easier to write Haskell
programs in Haskell than in Lisp.  That's not surprising.  I think you'll
also find that it's easier to write Lisp programs in Lisp than in Haskell.
To appreciate any language you must learn not only its syntax and semantics
but also something of its style.

BTW, you should take a look as Scheme; I think you'll like it better than
Common Lisp.  It doesn't need FUNCALL, local functions are defined by
LET/LETREC, etc.

Barry Shelton
·····@ute.columbiasc.ncr.com

Standard disclaimer.
From: Barry Margolin
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <1n80psINN4ph@early-bird.think.com>
In article <············@cs.cmu.edu> ····@cmu.edu (Chris Paris) writes:
>Once we have a clear and correct program in Haskell, it's time
>to convert it to lisp, and Oh My Gawd, we run into the following
>problems that make us write lisp code that's much much harder to
>understand than the equivalent Haskell code.
>
>1. no pattern matching (destructuring-bind isn't real pattern matching)

There are many available portable pattern matchers (some of the earliest
Lisp programs were pattern matchers).  I don't see why the application
becomes "much much harder to understand" just because the pattern matcher
comes from a library rather than built into the language.

>2. no (transparent) support for curried function application

Under what circumstances are curried functions needed for real-world
programming?  They always seemed to me to be more of an academic issue for
programming theorists.

>3. magic difference between functions and symbols that are bound to
>   lambda abstractions. I.e., you have to funcall the latter and not
>   the former.

This is a religious issue that's been discussed to death.

>4. (most annoying of all) can't define local functions and local
>   variables at the same level. You have to nest flet/labels and
>   let/let*.

So?  If the additional two columns of indentation is the most annoying
misfeature of Common Lisp, that's pretty good.
-- 
Barry Margolin
System Manager, Thinking Machines Corp.

······@think.com          {uunet,harvard}!think!barmar
From: David M Goblirsch
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <1993Mar5.194123.10405@linus.mitre.org>
In article <············@early-bird.think.com> ······@think.com (Barry Margolin) writes:

>>2. no (transparent) support for curried function application
>
>Under what circumstances are curried functions needed for real-world
>programming?  They always seemed to me to be more of an academic issue for
>programming theorists.
>

I am a "real-world" programmer, and I find curried functions very
useful.  I don't know if they are "needed", but I use curried functions
and partial applications in my scripts a lot.
--
David M. Goblirsch (the "Haskell Rascal")  ·····@mitre.org
The MITRE Corporation, McLean VA 22102
voice: (703) 883-5450
fax:   (703) 883-6708
From: Thorsten Altenkirch
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <ALTI.93Mar9171315@tanera.dcs.ed.ac.uk>
Certainly idological debates become very boring quickly.
However, I'd like to express my surprise that there are still
people having views as expressed by Barry Margolin. 

I should add that I once earned my money by writing LISP programs and
I did like CommonLisp quite a lot. In particulary because there is
a coherent set of predefined functions which is part of the language
and is quite nicely described in Steele's book. 

In article <············@early-bird.think.com> ······@think.com (Barry Margolin) writes:

   >
   >1. no pattern matching (destructuring-bind isn't real pattern matching)

   There are many available portable pattern matchers (some of the earliest
   Lisp programs were pattern matchers).  I don't see why the application
   becomes "much much harder to understand" just because the pattern matcher
   comes from a library rather than built into the language.

Actually I never used such a pattern matcher in LISP, but agree that
in principle it would be possible to implement such a beast on the
macro expansion level. It also seems to me that you rather think of a
pattern matching program as used in AI than the sort of things which
are relevant for program preprocessing.

Pattern matching in ML is an inherent feature of the programming
language and I believe this is a better design decision. When I wrote
my first ML programs (coming form LISP) I found the pattern matching
is, apart from polymorphic type inference, the distinguishing feature of
ML programs which makes them much easier to read than the
corresponding LISP program.

Actually a compiler can/should use the information inherent in
pattern matching to produce more efficient code. This would be at
least much more difficult if we expand the program first in
ordinary LISP code and then compile it.

   >2. no (transparent) support for curried function application

   Under what circumstances are curried functions needed for real-world
   programming?  They always seemed to me to be more of an academic issue for
   programming theorists.

Bullshit! Actually even the name of the function 1+ in Common Lisp
proposes than one would like to have currying, e.g. in ML you just
write ((op +) 1). (op is to uninfix +). 

   >3. magic difference between functions and symbols that are bound to
   >   lambda abstractions. I.e., you have to funcall the latter and not
   >   the former.

   This is a religious issue that's been discussed to death.

So you still believe in the devil and the virginity of Mary or what?
My impression was that even in CommonLisp this is just so for
historical compatibility. 

I have lost the original posting, so I will hope that the advantages
of compile time type checking regarding clarity of expression, safety
and efficiency of code have been mentioned there. 

After all I come to the conclusion that Barry hasn't really used both
styles of programming.

   -- 
   Barry Margolin
   System Manager, Thinking Machines Corp.

   ······@think.com          {uunet,harvard}!think!barmar

--

 Thorsten Altenkirch         	And there's a hand, my trusty fiere,
 Laboratory for Foundations  	   And gie's a hand o' thine,
 of Computer Science 	      	And we'll tak a right guid-willie waught
 University of Edinburgh     	   For auld lang syne!
From: 55837-larry mayka(warren)549
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <LGM.93Mar10094716@hermit.ATT.COM>
In article <·················@tanera.dcs.ed.ac.uk> ····@dcs.ed.ac.uk (Thorsten Altenkirch) writes:

      >2. no (transparent) support for curried function application

      Under what circumstances are curried functions needed for real-world
      programming?  They always seemed to me to be more of an academic issue for
      programming theorists.

   Bullshit! Actually even the name of the function 1+ in Common Lisp
   proposes than one would like to have currying, e.g. in ML you just
   write ((op +) 1). (op is to uninfix +). 

The following definition seems reasonable enough to me:

(defun curry (func &rest some-args)
  #'(lambda (&rest more-args)
    (apply func (append some-args more-args))))

An example of its usage:

> (curry '+ 1)
#<Closure 1 subfunction of CURRY>
> (curry * 2)
#<Closure 1 subfunction of CURRY>
> (curry * 3)
#<Closure 1 subfunction of CURRY>
> (curry * 4)
#<Closure 1 subfunction of CURRY>
> (funcall * 5 6)
21

      >3. magic difference between functions and symbols that are bound to
      >   lambda abstractions. I.e., you have to funcall the latter and not
      >   the former.

      This is a religious issue that's been discussed to death.

   So you still believe in the devil and the virginity of Mary or what?

Anti-religious slurs undermine your credibility.

   My impression was that even in CommonLisp this is just so for
   historical compatibility. 

Some of us very much prefer separate SYMBOL-FUNCTIONs and
SYMBOL-VALUEs.  Those who don't are free to use FUNCALL ubiquitously,
and even to hide its usage via a read-macro (e.g., defining [] to be
like () except with an implicit FUNCALL).


        Lawrence G. Mayka
        AT&T Bell Laboratories
        ···@iexist.att.com

Standard disclaimer.
From: Jeff Dalton
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <8552@skye.ed.ac.uk>
In article <·················@tanera.dcs.ed.ac.uk> ····@dcs.ed.ac.uk (Thorsten Altenkirch) writes:

>In article <············@early-bird.think.com> ······@think.com (Barry Margolin) writes:
>
>   >
>   >1. no pattern matching (destructuring-bind isn't real pattern matching)
>
>   There are many available portable pattern matchers (some of the earliest
>   Lisp programs were pattern matchers).  I don't see why the application
>   becomes "much much harder to understand" just because the pattern matcher
>   comes from a library rather than built into the language.
>
>Actually I never used such a pattern matcher in LISP, but agree that
>in principle it would be possible to implement such a beast on the
>macro expansion level.

It's also possible in practice, since several people have implemented
them.

>Pattern matching in ML is an inherent feature of the programming
>language and I believe this is a better design decision. 

It's only better if it has better consequences.  In Lisp it doesn't
make much difference.

>      When I wrote
>my first ML programs (coming form LISP) I found the pattern matching
>is, apart from polymorphic type inference, the distinguishing feature of
>ML programs which makes them much easier to read than the corresponding
>LISP program.

I find ML harder to read than Lisp.

Also, pattern-matching as it is actually provided in most of the
languages that have it (eg, ML, Prolog) suffers very seriously from
using positional notation.  You have to remember what, say, the
third argument to a constructor is; and if you ever change what
an argument is to add an additional one, you may have change patterns
all over the place.  You're going to _need_ pretty good type-checking
in a language like that.

>Actually a compiler can/should use the information inherent in
>pattern matching to produce more efficient code. This would be at
>least much more difficult if we expand the program first in
>ordinary LISP code and then compile it.

Why?  Do you think the type information is lost?

of course, there's less type information in Lisp than in ML, but
that's completely separate from whether or not there's pattern-matching.

>   >2. no (transparent) support for curried function application
>
>   Under what circumstances are curried functions needed for real-world
>   programming?  They always seemed to me to be more of an academic issue for
>   programming theorists.
>
>Bullshit! Actually even the name of the function 1+ in Common Lisp
>proposes than one would like to have currying, e.g. in ML you just
>write ((op +) 1). (op is to uninfix +). 

I have hardly ever used 1+ in cases where I would have otherwise
have wanted to partially apply +.  That is, I sometimes write 
(1+ x) instead of (+ 1 x), but I hardly ever write #'1+ instead
of #'(lambda (x) (+ 1 x)).

>I have lost the original posting, so I will hope that the advantages
>of compile time type checking regarding clarity of expression, safety
>and efficiency of code have been mentioned there. 

All things considered, I still prefer Lisp to ML.  Type checking
is useful, but I get most of the benefits from the kind of checking
that Lisp compilers do, but w/o paying the costs.

-- jd
From: Thomas M. Breuel
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <TMB.93Apr3205314@arolla.idiap.ch>
>>>>> On 2 Apr 93 18:44:44 GMT, ····@aiai.ed.ac.uk (Jeff Dalton) said:
> Also, pattern-matching as it is actually provided in most of the
> languages that have it (eg, ML, Prolog) suffers very seriously from
> using positional notation.  You have to remember what, say, the
> third argument to a constructor is; and if you ever change what
> an argument is to add an additional one, you may have change patterns
> all over the place.  You're going to _need_ pretty good type-checking
> in a language like that.

Positional notation is also used all over the place in Lisp.  Both
Lisp and SML provide alternatives. In SML, you would write something
like:

   Feature{x=3.0,y=9.7,name="corner-17",type=CORNER,orientation=0.2}

Pattern matching on such data structures is very useful and does
not require changes when the data structure is extended:

   fun f(Feature{orientation=a,...},eps) = ...

					Thomas.
From: Jeff Dalton
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <8561@skye.ed.ac.uk>
In article <················@arolla.idiap.ch> ···@idiap.ch writes:
>>>>>> On 2 Apr 93 18:44:44 GMT, ····@aiai.ed.ac.uk (Jeff Dalton) said:
>> Also, pattern-matching as it is actually provided in most of the
>> languages that have it (eg, ML, Prolog) suffers very seriously from
>> using positional notation.  You have to remember what, say, the
>> third argument to a constructor is; and if you ever change what
>> an argument is to add an additional one, you may have change patterns
>> all over the place.  You're going to _need_ pretty good type-checking
>> in a language like that.
>
>Positional notation is also used all over the place in Lisp.  

But it's not used for data structures in the same way, to the
same extent (especially compared to Prolog, I suspect).  Of
course Lisp programs used to use positions-in-lists a lot more
than they do now.  That's one of the reasons I was so surprised
when I saw what people were doing in Prolog.

In any case, pattern matching does have this problem (unless
it supports some kind of abstract "views"), and consequently this
supposed advantage of certain languages can actually be a 
disadvantage.

>Both Lisp and SML provide alternatives. In SML, you would write something
>like:
>
>   Feature{x=3.0,y=9.7,name="corner-17",type=CORNER,orientation=0.2}

Could, but often don't.

-- jd
From: Charlie Krasic -- Buck
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <CCKRASIC.93Apr6134709@plg.plg.uwaterloo.ca>
In article <····@skye.ed.ac.uk> ····@aiai.ed.ac.uk (Jeff Dalton) writes:

    [previous comments on weakness/strength of pattern matching removed]
>
>   >Both Lisp and SML provide alternatives. In SML, you would write something
>   >like:
>   >
>   >   Feature{x=3.0,y=9.7,name="corner-17",type=CORNER,orientation=0.2}
>
>   Could, but often don't.
>
>   -- jd

Says who?  I do this kind of thing all the time.  Usually, the only time
I rely on positional pattern match is when used in conjunction with
a data-constructor:

e.g. [in SML]:

datatype foo = FOO of int * real
	....

fun bar(FOO(i,r)) = ...
  | bar ...

Here, I don't care so much about using explicitly named fields since
the constructor FOO allows the typechecker to catch a mistake.

If FOO were defined such that is contained multiple fields of the same
type [say (int * int * real) instead of (int * real)], then I would 
use record notation (explicit names) instead of tuple notation to avoid
a possible mistake on the my part; i.e. to avoid confusing the roles of
the two ints.

-- Charlie


--
Charlie Krasic                  \Programming Language Group
                                 \Dept. of Computer Science
email: ········@plg.UWaterloo.ca  \  University of Waterloo
Phone: (519) 888-4822              \ Waterloo, Ont. N2L 3G1
From: Thomas M. Breuel
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <TMB.93Apr6220820@arolla.idiap.ch>
>>>>> On 6 Apr 93 14:21:22 GMT, ····@aiai.ed.ac.uk (Jeff Dalton) said:
>[···@idiap.ch said:]
>>Both Lisp and SML provide alternatives. In SML, you would write something
>>like:
>>
>>   Feature{x=3.0,y=9.7,name="corner-17",type=CORNER,orientation=0.2}

> Could, but often don't.

That's sort of like saying "I don't use DEFSTRUCT, I still use LIST
and C[AD]*R". If you use positional notation for non-trivial
constructors or destructuring (in either Lisp or SML), you only
have to blame your programming style for it, not the language.

					Thomas.
From: Richard A. O'Keefe
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <16921@goanna.cs.rmit.oz.au>
In article <············@cs.cmu.edu>, ····@cmu.edu (Chris Paris) writes:
> Once we have a clear and correct program in Haskell, it's time
> to convert it to lisp, and Oh My Gawd, we run into the following
> problems that make us write lisp code that's much much harder to
> understand than the equivalent Haskell code.

This is a lot like saying "Ada must be bad because when I design an
algorithm in C, Oh My Gawd we have such problems transliterating it
into Ada."  I'm serious about that.

> 1. no pattern matching (destructuring-bind isn't real pattern matching)

Well, pattern matching is only syntactic sugar after all.
The functional programming literature is full of descriptions of how to
compile that away.  There is at least one implementation of this for
Scheme.

> 2. no (transparent) support for curried function application

So?
    ;; Scheme
    (define (curry F x)
        (lambda Args (apply F `(,@Args ,x)) ))
    ;; or more efficiently, to curry a function of N arguments
    (define (curry-1 F x1)
        (lambda () (F x1)))
    (define (curry-2 F x2)
        (lambda (x1) (F x1 x2)))
    (define (curry-3 F x3)
        (lambda (x1 x2) (F x1 x2 x3)))
    ;; ...

    ;; Common Lisp
    (defun curry-1 (F x1)
        #'(lambda () (funcall F x1)))
    (defun curry-2 (F x2)
        #'(lambda (x1) (funcall F x1 x2)))
    (define curry-3 (F x3)
        #'(lambda (x1 x2) (funcall F x1 x2 x3)))
    ;; ...

To use these things:
    ;; Scheme
    ((curry-1 (curry-2 (curry-3 + A) B) C))	;=> (+ A B C)
    ;; Common Lisp
    (funcall (curry-1 (curry-2 (curry-3 #'+ A) B) C))

Of course, if you know that you want to transliterate to Lisp later
on, ML and Haskell don't *FORCE* you to use curried functions.  Why
not adopt a style that _will_ translate easily?

> 3. magic difference between functions and symbols that are bound to
>    lambda abstractions. I.e., you have to funcall the latter and not
>    the former.

I think you might prefer Scheme.  It does what you want.

> 4. (most annoying of all) can't define local functions and local
>    variables at the same level. You have to nest flet/labels and
>    let/let*.

I think you might prefer Scheme.  It does what you want.
It is worth pointing out, though, that it can't do you any harm.
Consider the Scheme block
    (letrec ((id-1 expr-1)
             ...
             (id-n expr-n))
        <body>)
Now the right hand sides of the expressions are evaluated in an unspecified
order, so you can partition the right hand sides into two sets:
    - ones that do not depend on other variables in the letrec
      (which can be moved out)
    - ones that DO depend on other variables
      (which must be functions)
So it is always possible (Scheme, Lisp, and SML being strict languages)
to convert a letrec into an outer let binding variables and an inner
letrec binding functions.  I have *never* experienced this as any kind
of inconvenience at all.  It must be a style difference.

An example of what you can do in Scheme:  I needed a parser for some data.
My definition took the form

    (define my-read "forward")
    (let ()
	(define var val)
	...
	(define (fun args) body)
	...
	;; That's the definitions done.  Now export the main function
	(set! my-read (lambda (port) ...))
	'my-read)	; return value of 'let'

The Scheme report explains how internal definitions can be eliminated in
favour of letrec.

> I'd like to know if anyone
> has written a macro package to do anything on my list, or in general,
> to make lisp more friendly.

Common Lisp is not the only Lisp.  Except for pattern matching, Scheme
comes close to what you want.  Scheme also served as the basis for
EU-lisp, for which there is a free prototype (FEEL).  The big question is
WHY is your friend using Lisp?  If you and your friend want to write SML,
SML/NJ and CAML Lite exist.  If your friend wants to learn how to write
Lisp, then it would pay to cultivate a Lisp style.
From: Andrew Wright
Subject: Re: Why lisp is not my favorite programming language
Date: 
Message-ID: <C3n0nD.96H@rice.edu>
In article <·····@goanna.cs.rmit.oz.au> ··@goanna.cs.rmit.oz.au (Richard A. O'Keefe) writes:
>Well, pattern matching is only syntactic sugar after all.
>The functional programming literature is full of descriptions of how to
>compile that away.  There is at least one implementation of this for
>Scheme.

...

>Common Lisp is not the only Lisp.  Except for pattern matching, Scheme
>comes close to what you want.

I'll be releasing a fairly sophisticated pattern matching system for
Scheme within the next week or two.  Stay tuned.

Andrew Wright