[comp.lang.lisp] FUNCALL question

barr@bbn.com (Hunter Barr) (02/02/90)

In article <385@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:

...

>Scheme has a FUNCALL only insofar as its semantics for calling functions
>are the same as the semantics of funcall.  Scheme does not have a
>function which does what FUNCALL does.  This may seem trivial, but my experience
>has been that the existence of FUNCALL (and FUNCTION and FLET and #', etc.)
>is the source of a great deal of confusion for beginning programmers,
>a great deal of frustration for experienced ones, and a lot of wasted time
>and effort implementing compilers which are more complicated than they
>need to be.  If anyone knows of a good reason to have an explicit FUNCALL
>(which is to say, a good reason to distinguish between a symbol's function
>binding and value binding) I wish they would point it out to me (preferably
>via E-mail).
>
>As long as I am picking on Common Lisp, let me air another of my pet peeves:
>There seems to be no way to undo the global special declaration performed
>by a DEFVAR.  Once a symbol has been DEFVARed, there is no way to use that
>symbol as a lexical variable ever again short of rebooting the environment.
>You can really screw yourself over with a careless DEFVAR.  This can be the
>source of some EXTREMELY subtle and frustrating bugs.
>
>-Erann Gat  (gat@robotics.jpl.nasa.gov)


The whole discussion of FUNCALL boils down to this: Erann doesn't like
Common Lisp overloading symbols by allowing separate value and
function cells.  Erann deserves no criticism for that.  I myself agree
that Scheme's scheme is much prettier in many ways.  But in my actual
work I usually find it more convenient to overload symbols.  (Keep in
mind that this says more about my personal style of programming and
thinking about problems than about anything else.)  But some problems
*are* harder to untangle if you let your symbols get overloaded, while
other problems are harder if you are forced to spend time thinking up
different (but related) symbol-names for variables and associated
functions.  Neither paradigm works best in all situations.

Now, about your pet peeve.  DEFVAR is intended to be quite permanent,
and there should not be an approved way to undo it.  If you need
something to be special, but you don't want to screw up your global
toplevel environment, don't do a DEFVAR.  Instead, just declare it to
be special inside the toplevel function of your system.  Give it the
customary stars to make it clear that you intend it to be special.
Try this:

<cl> (defun peeve-test ()
       (let ((*peeve* 'pet))
	 (declare (special *peeve*))
	 (peeve-1)))
peeve-test
<cl> (defun peeve-1 ()
       (describe '*peeve*))
peeve-1
<cl> (peeve-1)
*peeve* is a symbol
  It is unbound
  It is internal in the user package
<cl> (peeve-test)
*peeve* is a symbol
  Its value is pet
  It is internal in the user package
<cl> (peeve-1)
*peeve* is a symbol
  It is unbound
  It is internal in the user package
<cl> 

See?  Special variables with no mess left over.  Even if you use
DEFVAR, if you follow the star-tradition you can avoid trouble by
never trying to use *<foo>* as a lexical variable.  You wouldn't want
to (UN-DEFVAR *PRINT-BASE*) would you?  Now that *would* cause some
problems. 

Thanks for reading this far, everyone.
-- 
                            ______
                            HUNTER

buff@pravda.gatech.edu (Richard Billington) (02/02/90)

In article <386@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:
>In article <1655@skye.ed.ac.uk>, jeff@aiai.ed.ac.uk (Jeff Dalton) writes:
>> Indeed, an identifier can be associated with two values at once,
>> one when it's interpreted as a function name, the other when it's
>> interpreted as a variable.  Erann Gat made the mistake of calling
>> these two interpretations the symbol-function and symbol-value
>> when those terms are properly applied only to symbols (acting
>> as global variables and function names).  Local variables and
>> function names don't have symbol-values or symbol-functions in
>> that sense.  
>
>I want to thank Jeff Dalton for coming to my defense.  However, the
>above is totally incorrect (said with a smile).  Temporary variables
>do have value and function bindings.  That is why there are LET and
>FLET forms in CL.  For example:
>
>(flet ((x (x) (+ x x)))
>  (let ((x 1))
>    (x x)))
> ...

Hmmm, well there is certainly something more to what Jeff says than
your example allows. The point he makes is that temporary variables
are not equivalent to symbols, so his summary sentence is correct.
What he said does not preclude your example.

It is an important distinction to keep in mind. Forgetting that local
variables are not symbols, I wrote a stupid piece of cute code which
looked like the following:

(defun foo (x)	
  (flet ((hi () (print "hi there"))	;same for labels
         (bye () (print "good-bye")))
    (funcall x)))

and then got an error (that the function hi is undefined) when I
tried the following:

(foo 'hi)

Whereas the following works fine:

(defun hi () (print "hi there"))

(defun foo (x) (funcall x))

(foo 'hi) => "hi there"

This actually led me to some confusing results that only the rule
"local variables are not symbols" helped explain in anyway. Given
my first definition of foo, consider

(defun foo1 ()
  (flet ((hi () (print "hi there"))	;same for labels
         (bye () (print "good-bye")))
    (funcall 'hi)))

(defun foo2 ()	
  (flet ((hi () (print "hi there"))	;same for labels
         (bye () (print "good-bye")))
    (funcall #'hi)))

foo2 works, foo1 doesn't. Now consider

(defun foo3 (x)
  (let ((hi #'(lambda () (print "hi there")))
        (bye #'(lambda () (print "hi there"))))
    (funcall x)

This does work.

Having played around with this a bit, one thing is clear
to me local variables are not equivalent to symbols.

jeff@aiai.ed.ac.uk (Jeff Dalton) (02/02/90)

In article <386@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:
>In article <1655@skye.ed.ac.uk>, jeff@aiai.ed.ac.uk (Jeff Dalton) writes:
>> Indeed, an identifier can be associated with two values at once,
>> one when it's interpreted as a function name, the other when it's
>> interpreted as a variable.  Erann Gat made the mistake of calling
>> these two interpretations the symbol-function and symbol-value
>> when those terms are properly applied only to symbols (acting
>> as global variables and function names).  Local variables and
>> function names don't have symbol-values or symbol-functions in
>> that sense.  

>I want to thank Jeff Dalton for coming to my defense.  However, the
>above is totally incorrect (said with a smile).  Temporary variables
>do have value and function bindings.  That is why there are LET and
>FLET forms in CL.  For example:

No, you have it wrong -- this time.  But it's because I failed to make
some things clear.

I tried to be careful to say "identifier" when I was talking about a
name in a program and "variable" and "function name" for the two
possible interpretations of identifiers (possible in the contexts we
were interested in, that is).  In this terminology, a _variable_
doesn't have both a function and value binding, but a single name
might have both, in a sense, because it's being used as both a
variable and a function name.

We could shift terminology, however, and say that a variable can
have both a value and a function binding (as you say above).  I
wasn't trying to disagree with you there.

However, once you say "symbol-value" and "symbol-function" people may
well assume you're talking about _symbols_ (the data objects) and the
associated values obtained by the Common Lisp functions SYMBOL-VALUE
and SYMBOL-FUNCTION.  Indeed, I thought people were reading you that
way.

The problem with talking this way is that local variables might not
be associated with symbols at all -- after compilation, for example.
And, in any case, the functions SYMBOL-VALUE and SYMBOL-FUNCTION can't
look at local variables.

Anyway, that's the "sense" I had in mind when I wrote "local variables
and function names don't have symbol-values or symbol-functions in
that sense."

-- Jeff

gat@robotics.Jpl.Nasa.Gov (Erann Gat) (02/02/90)

In article <1666@skye.ed.ac.uk>, jeff@aiai.ed.ac.uk (Jeff Dalton) writes:
> No, you have it wrong -- this time. 

I stand corrected, and I apologize for my careless use of the terms
symbol-value and symbol-function.  Nevertheless, I stand by the 
assertion that identifiers in Common Lisp, be they local or global,
have two bindings, a value binding and a function binding, and that
this is the reason for the existence of an explicit FUNCALL function,
that is, to enable one to call a function stored in an identifier's
value slot.

I also reaffirm my position that multiple bindings cause a great deal of
confusion!

-Erann

sandra%defun.utah.edu@cs.utah.edu (Sandra J Loosemore) (02/02/90)

In article <387@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:
>Nevertheless, I stand by the 
>assertion that identifiers in Common Lisp, be they local or global,
>have two bindings, a value binding and a function binding,

Agreed, but they actually have more than two bindings.  They can also
have type bindings, documentation-type bindings, declaration bindings,
and so on. 

>and that
>this is the reason for the existence of an explicit FUNCALL function,
>that is, to enable one to call a function stored in an identifier's
>value slot.

No, the reason for the existence of the FUNCALL function is that in
Common Lisp syntax, the CAR of a list follows different evaluation
rules than subforms in the CDR.  What FUNCALL buys you is the ability
to obtain the function to be called by evaluating something with the
CDR evaluation rules instead of the CAR evaluation rules.  Although
it's hard to imagine why one would want to do such a thing, you could
certainly have a two-namespace Lisp that uses the same evaluation
rules in both CAR and CDR, and no explicit FUNCALL operation.  You
would just have to use #'<function-name> as the CAR of every function
call form instead of just <function-name> so that you refer to the
functional binding of the name instead of its variable binding, as in

    (#'list 'a 'b 'c)

One can also imagine a single-namespace Lisp that has different 
evaluation rules for the CAR than the CDR, that would require an
explicit FUNCALL operator.  The issues of syntax and namespaces are
actually orthogonal.

>I also reaffirm my position that multiple bindings cause a great deal of
>confusion!

I don't think anybody has been seriously taking issue with this.  I'm
not too bothered by multiple namespaces in practice, but I agree that
a single namespace is less complicated.

-Sandra Loosemore (sandra@cs.utah.edu)

davis@ilog.UUCP (Harley Davis) (02/02/90)

 > > interpreted as a variable.  Erann Gat made the mistake of calling
 > > these two interpretations the symbol-function and symbol-value
 > > when those terms are properly applied only to symbols (acting
 > > as global variables and function names).  Local variables and
 > > function names don't have symbol-values or symbol-functions in
 > > that sense.  
 > 
 > I want to thank Jeff Dalton for coming to my defense.  However, the
 > above is totally incorrect (said with a smile).  Temporary variables
 > do have value and function bindings.  That is why there are LET and
 > FLET forms in CL.  For example:
 > 
 > (flet ((x (x) (+ x x)))
 >   (let ((x 1))
 >     (x x)))

The above is totally incorrect (:^)).  Jeff correctly pointed out that
lexically-scoped variables do not, properly speaking, have
symbol-values or symbol-functions, because these variables, despite
all appearances, are not symbols.  Special variables, on the other
hand, are symbols, to which symbol-function and symbol-value are
applicable.   The non-symbolhood of lexical variables permits nifty
compiler optimizations.

The following code is erroneous unless x has been proclaimed special:

(flet ((x (x) (+ x x)))
  (let ((x 1))
    (list (symbol-function x) (symbol-value x))))

[ref. CLtL edition 1 p. 90]

-- Harley

------------------------------------------------------------------------------
Harley Davis			internet: davis@ilog.fr
ILOG S.A.			uucp:  ..!mcvax!inria!davis
2 Avenue Gallie'ni, BP 85	tel:  (33 1) 46 63 66 66	
94253 Gentilly Cedex		
France

pk@tut.fi (Kellom{ki Pertti) (02/02/90)

It seems to me that the whole mess with funcall is caused by
implementations that extend the Common Lisp as defined by CLtL. The
confusion stems from the semantics of funcall. CLtL states that

"(funcall fn a1 a2 ... an) applies the function fn to the arguments
a1, a2, ..., an. [stuff about macros etc. deleted]"

Most Common Lisp implementations (Allegro, Kyoto, Symbolics among
others), however, extend the semantics by saying that if fn evaluates
to a symbol, then the *global* (yuch!) function definition of that symbol is
used. This causes a great deal of confusion, as can be seen from the
ongoing discussion. Specifically, some of the examples given by
Richard Billington work only because of this hack. (Please do not
understand me wrong: I can understand the reasoning behind it, it
just gives my schemy mind the shivers!)

>>>>> On 1 Feb 90 20:11:05 GMT, buff@pravda.gatech.edu (Richard Billington) said:
buff> (defun foo (x)	
buff>   (flet ((hi () (print "hi there"))	;same for labels
buff>          (bye () (print "good-bye")))
buff>     (funcall x)))

buff> and then got an error (that the function hi is undefined) when I
buff> tried the following:

buff> (foo 'hi)

Because funcall got the symbol 'hi' as the first argument, and didn't
find a global function definition for it.

buff> Whereas the following works fine:

buff> (defun hi () (print "hi there"))
buff> (defun foo (x) (funcall x))
buff> (foo 'hi) => "hi there"

Because this time there is a global function definition.

buff> (defun foo1 ()
buff>   (flet ((hi () (print "hi there"))	;same for labels
buff>          (bye () (print "good-bye")))
buff>     (funcall 'hi)))

buff> (defun foo2 ()	
buff>   (flet ((hi () (print "hi there"))	;same for labels
buff>          (bye () (print "good-bye")))
buff>     (funcall #'hi)))

buff> foo2 works, foo1 doesn't. Now consider

Same thing here, foo1 does not find a global function definition. foo2
works, because "within the body of the flet form, function names
matching those defined by flet refer to the locally defined function
rather than to the global definitions of the same name" (CLtL).

buff> (defun foo3 (x)
buff>   (let ((hi #'(lambda () (print "hi there")))
buff>         (bye #'(lambda () (print "hi there"))))
buff>     (funcall x)))                              

buff> This does work.

I got an error message from this (using Allegro CL 3.0.3). I suspect
that you had a global function called 'hi', and everything works as
before.

The thing that bothers my puritan mind here, is that somehow the
distinction between functions and symbols is blurred. In Scheme
everything is clear: a procedure is a procedure and a symbol is a
symbol. Once you introduce special treatment for some data types, you
get confusion because the language is no more logical. One thing that
surprises me is that CLtL does specify treatment for both functions
and symbols when given as arguments to apply (with the same semantics
as discussed before) but not for funcall.

I must say that this whole thing has really made me feel bad about CL.
Previously all I had against CL was it sheer size, but this funcall
stuff has really pissed me off. Using global function bindings seems
to me to violate all the nice rules of lexical scoping. To me it is
simply a dirty hack.

Moreover, the treatment of functions with all the special forms and
procedures seems to imply that functions in CL are not really first
class citizens, because one has to go thru a *lot* of trouble when
passing them around.

--
Pertti Kellom\"aki (TeX format)  #       These opinions are mine, 
  Tampere Univ. of TeXnology     #              ALL MINE !
      Software Systems Lab       #  (but go ahead and use them, if you like)

buff@pravda.gatech.edu (Richard Billington) (02/02/90)

In article <PK.90Feb2153658@kaarne.tut.fi> pk@tut.fi (Kellom{ki Pertti) writes:
>buff> (defun foo3 (x)
>buff>   (let ((hi #'(lambda () (print "hi there")))
>buff>         (bye #'(lambda () (print "hi there"))))
>buff>     (funcall x)))                              
>
>buff> This does work.
>
>I got an error message from this (using Allegro CL 3.0.3). I suspect
>that you had a global function called 'hi', and everything works as
>before.

Quite right. This was the only thing that really confused me, and it
was sloppy investigating on my part.

>Previously all I had against CL was it sheer size, but this funcall
>stuff has really pissed me off. Using global function bindings seems
>to me to violate all the nice rules of lexical scoping. To me it is
>simply a dirty hack.

Hmmm, I'm not so sure it violates lexical scoping. Now that you've pointed
out my error (in the above), it seems to me the behaviour observed in all
of my examples is quite consistant with lexical scoping: Within the function
definition, the local variable can be referenced with no problem. However,
if (as in my example) I try to reference a (dare I say) symbol which is
defined within the scope of the function I'm calling, I can't. Why? because
the name of the symbol in the calling environment (although identical in
print) is different from the name in the internal environment. The only
place where one must remember that local variables are not symbols is
in the case of (funcall 'x) because if x really was a symbol it would still
be hanging around and hence its functional definition would be available.
This, however, does not violate lexical scoping.

>Moreover, the treatment of functions with all the special forms and
>procedures seems to imply that functions in CL are not really first
>class citizens, because one has to go thru a *lot* of trouble when
>passing them around.

Whoever claimed that functions were first class citizens in any other lisp
than scheme - I thought that was the single biggest reason for bringing
scheme into existance: to have a clean implementation of the lambda calculus,
which lisp is NOT (even McCarthy agrees - making functions second class
citizens was a mistake).

>Pertti Kellom\"aki (TeX format)  #       These opinions are mine, 
>  Tampere Univ. of TeXnology     #              ALL MINE !
>      Software Systems Lab       #  (but go ahead and use them, if you like)

Richard Billington (buff@pravda.gatech.edu)

gat@robotics.Jpl.Nasa.Gov (Erann Gat) (02/03/90)

In article <PK.90Feb2153658@kaarne.tut.fi>, pk@tut.fi (Kellom{ki Pertti) writes:
> Most Common Lisp implementations (Allegro, Kyoto, Symbolics among
> others), however, extend the semantics [ of FUNCALL ]
> by saying that if fn evaluates
> to a symbol, then the *global* (yuch!) function definition of that symbol is
> used.

This is not an extension.  On page 32 of CLtL it says, "A symbol may serve
as a function; an attempt to invoke a symbol as a function causes the
contents of the symbol's [global] function cell to be used."

BTW, thanks to Jeff and Sandra for setting me straight on the distinction
between symbols and local indentifiers.  I really was confused on this
point!

E.

gat@robotics.Jpl.Nasa.Gov (Erann Gat) (02/03/90)

In article <2247@papaya.bbn.com>, barr@bbn.com (Hunter Barr) writes:
> You wouldn't want
> to (UN-DEFVAR *PRINT-BASE*) would you?  Now that *would* cause some
> problems. 

I see your point.  I guess my real gripe is that there is no way to
guarantee that a given variable is lexically scoped.  I would like
to be able to do something like:

(let ((x 1)) (declare (lexical x)) ...

but CL has no such declaration.  Granted, if you use the star convention
(and everyone else on your Lisp machine uses it too) then you probably
won't have problems.  (This 'solution' is strongly reminiscent of the
FORTRAN convention of having all variables beginning with I,J,K,L,M or
N be integers.)  However, the way things stand, one careless mistake or
ignorant user can require a LONG time to fix.  (One day long ago I
typed (defvar x 1) as part of a quick experiment on a TI Explorer
and for the next few days no one could understand why their code
suddenly didn't work.  Then someone rebooted the machine and all the
problems mysteriously vanished.)

E.

muehle@ssc-vax.UUCP (Eric Muehle) (02/03/90)

In article <387@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:

   I stand corrected, and I apologize for my careless use of the terms
   symbol-value and symbol-function.  Nevertheless, I stand by the 
   assertion that identifiers in Common Lisp, be they local or global,
   have two bindings, a value binding and a function binding, and that
   this is the reason for the existence of an explicit FUNCALL function,
                              ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
   that is, to enable one to call a function stored in an identifier's
   value slot.

   I also reaffirm my position that multiple bindings cause a great deal of
   confusion!

   -Erann

What about this:

(funcall #'(lambda (x) (1+ x)) 10)

I am passing a function to FUNCALL, not an identifier.  Being able to
call *functions* is the reason for the existence of FUNCALL.  If there 
was no FUNCALL then you can kiss all of your :test, :key, and any other
keywords that expects a FUNCTION for an argument goodbye.

ERIC MUEHLE

-- 
Eric Muehle            (require :standard-disclaimers)
Boeing Aerospace and Electronics  usenet: {world}!uw-beaver!ssc-vax!muehle
Seattle, WA               arpanet: ssc-vax!muehle@beaver.cs.washington.edu

mj@cs.brown.edu (Mark Johnson) (02/03/90)

gat@robotics.Jpl.Nasa.Gov writes:

> I guess my real gripe is that there is no way to
> guarantee that a given variable is lexically scoped.
> I would like to be able to do something like:
>
> (let ((x 1)) (declare (lexical x)) ...

I agree --- except that I think CL should be modified
so that all variables' values are determined using the
rules of lexical scoping, unless the variable reference
i explicitly identified as being dynamically scoped:
perhaps by using forms such as (dynamic x) or (special x).
(This is in addition to declaring the variable special
with defvar).  Syntactic sugar for these forms could
easily be devised --- perhaps #*x could expand to
(dynamic x) or whatever?

Mark

dorai@titan.rice.edu (Dorai Sitaram) (02/05/90)

In article <1654@skye.ed.ac.uk> jeff@aiai.UUCP (Jeff Dalton) writes:
$In article <385@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:
$>In article <1990Jan29.224305.20803@hellgate.utah.edu>, sandra%defun.utah.edu@cs.
$>utah.edu (Sandra J Loosemore) writes:
$>> Scheme has a FUNCALL operation with exactly the same *semantics* as
$>> that in Common Lisp.  It does, however, have different syntax, which
$>> most people would probably agree is less complicated.
$
$I'm not sure it's fair to say FUNCALL is just syntax, because FUNCALL
$is not restricted to appearing as the car of a function call. FUNCALL
							       ^^^^^^^
$is a function, and Scheme does not have such a function.  Since the
 ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
$original quesiton was "why is FUNCALL a function?", this is a relevant,
$although minor, point.
$
$I think it's true that most people now prefer the Scheme approach; but
$it depends, in part, on what sort of code is involved.  When a lot of
$FUNCALLs are needed, they can make code look cluttered and hard to
$read.  But when they're rare, they can act as a useful sign that
$something unusual is happening.
$
$>Scheme has a FUNCALL only insofar as its semantics for calling functions
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
$>are the same as the semantics of funcall.  Scheme does not have a
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
$>function which does what FUNCALL does.
  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
$
$I agree (see above).

I saw the above rather by accident, so what I say here might take
something out of context.  Disclaimer done, I don't see how someone
can claim that Scheme doesn't have a _funcall_ function (procedure).
Surely you don't just mean that the language standard doesn't mention
_funcall_?  For _funcall_ is easily retrieved as:

	(define funcall (lambda (f . z) (apply f z)))

So what am I missing?

--dorai
--
-------------------------------------------------------------------------------
It may be that the gulfs will wash us down;
It may be we shall touch the Happy Isles.
-------------------------------------------------------------------------------

jeff@aiai.ed.ac.uk (Jeff Dalton) (02/06/90)

In article <4541@brazos.Rice.edu> dorai@titan.rice.edu (Dorai Sitaram) writes:
 >In article <1654@skye.ed.ac.uk> jeff@aiai.UUCP (Jeff Dalton) writes:

 >$I'm not sure it's fair to say FUNCALL is just syntax, because FUNCALL
 >$is not restricted to appearing as the car of a function call. FUNCALL
 >							       ^^^^^^^
 >$is a function, and Scheme does not have such a function.  Since the
 > ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 >$original quesiton was "why is FUNCALL a function?", this is a relevant,
 >$although minor, point.

 >I saw the above rather by accident, so what I say here might take
 >something out of context.  Disclaimer done, I don't see how someone
 >can claim that Scheme doesn't have a _funcall_ function (procedure).
 >Surely you don't just mean that the language standard doesn't mention
 >_funcall_?  For _funcall_ is easily retrieved as:
 >
 >	(define funcall (lambda (f . z) (apply f z)))
 >
 >So what am I missing?

Presumably you don't think there's *no* difference between Scheme and
Common Lisp on this point.

What you seem to be missing is the difference between "unlike Common
Lisp, Scheme doesn't have a function called FUNCALL" and "FUNCALL
can't be defined in Scheme".  Maybe that's not quite what you're
missing, but you do seem to be replying to the second claim rather
than the first.

I suppose I am just saying the Scheme Report doesn't mention funcall,
but note that I did say it was a minor point.  Nonetheless, there are
some practical consequences.  That the language standard doesn't
mention funcall means that the user has to define it (if the user
wants it at all, which in Scheme is unlikely).

-- Jeff

jeff@aiai.ed.ac.uk (Jeff Dalton) (02/06/90)

In article <389@forsight.Jpl.Nasa.Gov> gat@robotics.Jpl.Nasa.Gov (Erann Gat) writes:
 >           However, the way things stand, one careless mistake or
 >ignorant user can require a LONG time to fix.  (One day long ago I
 >typed (defvar x 1) as part of a quick experiment on a TI Explorer
 >and for the next few days no one could understand why their code
 >suddenly didn't work.  Then someone rebooted the machine and all the
 >problems mysteriously vanished.)

Special variables aren't the only thing like this.  Try redefining CAR
or LIST, for example.

jeff@aiai.ed.ac.uk (Jeff Dalton) (02/06/90)

In article <19479@mephisto.UUCP> buff@pravda.UUCP (Richard Billington) writes:
>Whoever claimed that functions were first class citizens in any other lisp
>than scheme - I thought that was the single biggest reason for bringing
>scheme into existance: to have a clean implementation of the lambda calculus,
>which lisp is NOT (even McCarthy agrees - making functions second class
>citizens was a mistake).

I would say functons are 1st class in Common Lisp.  They can be passed
as arguments, returned as results, assigned to variables, included in
data structures and have indefinite lifetimes just like, say, lists.
What more is needed?  OK, they can't be read and printed, but they
can't in Scheme either.

(Note, though, that in CLtL '84 functions needn't be a distinct data
type -- eg, they might be lists.  I'm assuming that this will change.)

-- Jeff

jeff@aiai.ed.ac.uk (Jeff Dalton) (02/06/90)

In article <6904@ilog.UUCP> davis@ilog.UUCP (Harley Davis) writes:
>The following code is erroneous unless x has been proclaimed special:
>
>(flet ((x (x) (+ x x)))
>  (let ((x 1))
>    (list (symbol-function x) (symbol-value x))))
>
>[ref. CLtL edition 1 p. 90]

Um, isn't it erroneous even if X _has_ been proclaimed special?

For instance, in

     (list (symbol-function x) (symbol-value x))))

both SYMBOL-FUNCTION and SYMBOL-VALUE will complain because they're
being called on the number 1.  That will happen even if X is special.
We might try quoting X, but SYMBOL-FUNCTION will still complain,
because special declarations don't affect function bindings.

-- Jeff

gat@robotics.Jpl.Nasa.Gov (Erann Gat) (02/06/90)

In article <4541@brazos.Rice.edu>, dorai@titan.rice.edu (Dorai Sitaram) writes:
> 
> I saw the above rather by accident, so what I say here might take
> something out of context.  Disclaimer done, I don't see how someone
> can claim that Scheme doesn't have a _funcall_ function (procedure).
> Surely you don't just mean that the language standard doesn't mention
> _funcall_?  For _funcall_ is easily retrieved as:
> 
> 	(define funcall (lambda (f . z) (apply f z)))
> 
> So what am I missing?

What you (and Eric Meuhler, author of article 1753) are both missing
is about twenty articles of discussion which preceeded the postings
to which you reply.  In fact, that the Scheme language standard
does not mention FUNCALL is EXACTLY what I meant, and if you had gone
back and read the reference articles (or sent me E-mail) you could have
found this out without broadcasting the fact that you hadn't done your
homework.

E.