Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Question: macros and lambdas

46 views
Skip to first unread message

Jacek Podkanski

unread,
Sep 27, 2002, 4:57:30 AM9/27/02
to
Hi,

I'm quite new to Lisp. At the moment I'm trying to understand some of its
concepts. Somewhere I seen information that everything that can be done
with macros can be done with lambdas. Is this correct? Can anybody point
out differences between the two?

Regards
--
Jacek Podkanski

Erik Naggum

unread,
Sep 27, 2002, 7:31:49 AM9/27/02
to
* Jacek Podkanski

| I'm quite new to Lisp.

Welcome!

| At the moment I'm trying to understand some of its concepts.

Commendable to understand first and judge later. Disturbingly many judge
first and therefore never understand.

| Somewhere I seen information that everything that can be done with macros
| can be done with lambdas. Is this correct?

It is an arbitrary statement devoid of contents and meaning, so therefore
neither correct nor incorrect.

| Can anybody point out differences between the two?

Yes, but it would be meaningless to you until you are experienced with Lisp.

Forget the statement entirely and proceed to learn Lisp as if you had never
heard it. You will be much better off than prematurely trying to attach
meaning to this statement.

--
Erik Naggum, Oslo, Norway

Act from reason, and failure makes you rethink and study harder.
Act from faith, and failure makes you blame someone and push harder.

Tim Bradshaw

unread,
Sep 27, 2002, 7:56:17 AM9/27/02
to
* Jacek Podkanski wrote:
> I'm quite new to Lisp. At the moment I'm trying to understand some of its
> concepts. Somewhere I seen information that everything that can be done
> with macros can be done with lambdas. Is this correct? Can anybody point
> out differences between the two?

I think that the term `everything can be done with x' needs to be
clarified. As it stands it is altogether too close to some kind of
Turing equivalence notion which is not really useful in context.

Essentially macros in Lisp are source to source transformations which
are themselves specified in Lisp. These transformations are rather
easy to express because of the facts that Lisp source code is
represented as a Lisp data structure; Lisp has so little syntax - so
there is no upfront commitment to what a given bit of source `means'
in the sense that `{...}' is a block in C; and finally that lisp does
not have a distinction between expressions and statements in the
language. Thus, rather than the limited `string-replacement' macros
that, say, C has, Lisp macros allow almost completely general rewrites
of the structure of a bit of source code, and the code that implements
the macro works in terms of the structure of the source, not some
stringy representation.

All of this makes Lisp macros extremely powerful and flexible tools.
The result of having them is that you can extend the `syntax' of the
language to introduce, say, new control constructs or binding forms,
or ultimately to create a whole lisp-like language on top of Lisp.
And all of this can be done incrementally - there's never a point
where you have to sit down with yacc and lex and write a parser for
your new language.

The result of this is that substantial Lisp programs tend to evolve
all sorts of domain-specific `slang' which expresses very succinctly
the concepts used in the domain. For instance, in a system I've
written recently I have things like:

(with-session ()
;; in here there is a notion of `session variables' which are a
;; bit like shell variables
... code ...)

(with-io-session ()
;; in here you can open and access named `output viewers' which correspond
;; to windows on the screen (typically) which display random
;; text you send them. At the end of this scope all these
;; windows will be closed (unless the IO session has been `captured').
... code ...)

;;; define a hook named FOO
(define-hook foo)

(define-hook-named bar foo ()
;; define a bit of code on the FOO hook called BAR. If this is
;; evaluated more than once then the BAR code will be replaced
;; with the new stuff. Everything gets compiled if the source
;; file is compiled.
... code ...)

;;; Run all the code on the FOO hook, passing no arguments.
;;; This isn't a macro, it's just a function...
(run-hook 'foo :args '())

Macros are sometimes fairly fiddly to write as you have to both think
in a fairly unconventional way - in terms of things that take source
and rewrite it &c, and you also have to be aware of various issues
which the system might not protect you from, such as name capture
issues (some macro systems do protect you from these issues, and you
will see incessant bickering about how ones that don't are not good
&c). Writing macros is programming language design, and that is not
easy.

OK, so now the equivalence stuff. Well for one, clearly macros don't
buy you some new formal power - the language is just turing equivalent
anyway. But another thing is that, if you had a Lisp without a macro
system, you could pretty much write one. For instance, if you were
happy with a file-based system, you could write a program which read
(using READ) a source file, form by form, and then processed it with a
function called, say, EXPAND which implemented the user-written macro
system, and then evaluated the result. The same could clearly be done
for an interactive sytem:

(loop
(print (simple-eval (expand (read)))))

where SIMPLE-EVAL is something that doesn't understand macros, and
EXPAND is the user macro expander function. EXPAND is fiddly to
write, but not that fiddly.

So if you didn't have macros, you could implement them - the really
crucial thing is READ, and source code being data. Indeed this is
almost certainly how the first Lisp macro systems *were* written.

But just because you *could* do it doesn't mean you should *want* to,
of course.

--tim

Joe Marshall

unread,
Sep 27, 2002, 11:07:13 AM9/27/02
to
Jacek Podkanski <jacekpo...@supanet.com> writes:

> Hi,
>
> I'm quite new to Lisp. At the moment I'm trying to understand some of its
> concepts. Somewhere I seen information that everything that can be done
> with macros can be done with lambdas. Is this correct?

If it were, why do languages with lambdas have macros?

There are several uses (and abuses) of macros, and some of these can
be trivially expressed using lambda and quote expressions. But
consider a macro such as DEFSTRUCT.

(macroexpand '(defstruct foo (slot-a nil)))

=>

(PROGN
(SETF (GET 'FOO :STRUCT-TEMPLATE)
#1=#(FOO #<Standard-Class FOO #xA30820>
NIL NIL 0 1 SLOT-A NIL))

(DEFUN MAKE-FOO (&KEY (SLOT-A NIL))
(LET* ((#:G1376 (ALLOC-UVECTOR 2 2)))
(SETF (UREF #:G1376 1) #1#)
(SETF (UREF #:G1376 2) SLOT-A) #:G1376))

(SETF (GET 'FOO ':STRUCT-CONSTRUCTOR) 'MAKE-FOO)

(DEFUN COPY-FOO (ARG)
(CLONE-STRUCT ARG))

(DEFUN FOO-P (ARG)
(STRUCT-TYPE-P ARG 'FOO))

(DECLARE-TYPE-SPECIFIER FOO (X SPECIFIER)
(DECLARE (IGNORE SPECIFIER))
(STRUCT-TYPE-P X 'FOO))

(DEFUN FOO-SLOT-A (ARG)
(CHECK-STRUCT-TYPE ARG 'FOO)
(UREF ARG 2))

(DEFUN (SETF FOO-SLOT-A) (VALUE ARG)
(CHECK-STRUCT-TYPE ARG 'FOO)
(SETF (UREF ARG 2) VALUE))

'FOO)

Barry Margolin

unread,
Sep 27, 2002, 11:20:07 AM9/27/02
to
In article <1y7fzd...@ccs.neu.edu>, Joe Marshall <j...@ccs.neu.edu> wrote:
>Jacek Podkanski <jacekpo...@supanet.com> writes:
>
>> Hi,
>>
>> I'm quite new to Lisp. At the moment I'm trying to understand some of its
>> concepts. Somewhere I seen information that everything that can be done
>> with macros can be done with lambdas. Is this correct?
>
>If it were, why do languages with lambdas have macros?

Syntactic sugar.

Compare:

(defun if-function (test then-func else-func)
(cond (test (funcall then-func))
(t (funcall else-func))))

(if-function (> x y)
(lambda () (format t "X is greater than Y~%"))
(lambda () (format t "X is not greater than Y~%")))

(defmacro if-macro (test then-expression else-expression)
`(cond (,test ,then-expression)
(t ,else-expression)))

(if-macro (> x y)
(format t "X is greater than Y~%")
(format t "X is not greater than Y~%"))

This is clearly a very simple example, and the differences aren't extreme.
But try to imagine doing something like LOOP in a totally functional
manner. It's possible, but it probably wouldn't be pretty (then again,
some people don't consider LOOP to be pretty in the first place, so maybe
the power and flexibility that Lisp macros provides has a downside).

--
Barry Margolin, bar...@genuity.net
Genuity, Woburn, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.

Kaz Kylheku

unread,
Sep 27, 2002, 12:56:57 PM9/27/02
to
Jacek Podkanski <jacekpo...@supanet.com> wrote in message news:<56Vk9.2190$sh4.1...@newsfep2-win.server.ntli.net>...

It is only correct in the sense that everything that can be done with
A can be done with a Turing equivalent B. That says nothing about the
relative convenience, expressibility and ultimate human effort.

People who say that anything that can be done with A can also be done
with B, and therefore A is not needed, usually have some agenda, like
promoting an environment whose designers and implementors didn't
anticipate the need for A.

Lambdas are functions. Functions transform data. Macros are functions
also, but the data which they transform is the program's syntax.
Transformations on syntax support the ability to invent arbitrary
computational abstractions, because the programmer can assign any
meaning whatsoever to a syntax.

Transformations on data (that is not code) provide only a limited
ability to create procedural abstractions. The user of the function
must deal with the function's protocol: it expects input data in a
certain format, and produces data in a certain format. A function call
cannot do many simple things, such as establish the binding for a
lexical variable.

The only way in which a function can compete with a macro is if it
implements an interpreter for an expression, which is passed in as an
argument. But then the problem is, in what environment will that
expression be transformed and evaluated? Macros have the ability to do
the transformation outside of the program, in a sense, and substitute
the result in the place of the macro call. A function (in Lisp)
doesn't have access to the environment from which it was called. So
for instance something like

(let ((x 3)) (custom-interpret-expression '(blorg x))

where custom-interpret-expression is a function that operates on the
expression '(blorg x), could never work right. The function would
transform the expression in its black box, which has no access to the
calling environment in which x is bound to 3. On the other hand, a
macro called blorg could do the job:

(let ((x 3)) (blorg x))

because it would take (blorg x), and transform it into open code that
is substituted in its place.

Now, custom-interpret-expression could take a parameter that is a
closure, a function-object that captures the binding:

(let ((x 3))
(custom-interpret-expression #'(lambda () (blorg x))))

But now the problem is that the function object generated by
#'(lambda...) is a black box. The function has no way to unpack it and
rewrite its code! So the embedded expression (blorg x) is simply taken
at face value. The only thing that custom-interpret-expression can do
is invoke the closure with funcall or whatnot. Sometimes this sort of
thing is exactly what you want; lexical closures are a powerful tool
that we don't want to be without. Macros and closures live in harmony.
For example, suppose you want to implement the macro (while condition
body), and you want to implement it using the smallest possible
translation. What you can do is have your macro generate closures out
of all the pieces that must be evaluated, and pass those closures down
to a function, so that the substituted transformation looks like:

(while-function #'(lambda () condition) #'(lambda () body))

Of course, the user of the macro is not aware that the condition
expression and body forms are packaged into closures and passed down
to a function that actually implements the looping behavior. So in
other words, macros can be used to form a smooth interface over a
clunky functional plumbing.

We had a higher-order-functions versus macros debate here recently,
and eventually the higher-order-functions proponents ran out of
arguments supporting the thesis that HOF's can replace macros. You
might want to dig that up.

Barry Margolin

unread,
Sep 27, 2002, 1:21:34 PM9/27/02
to
In article <56Vk9.2190$sh4.1...@newsfep2-win.server.ntli.net>,

Since you're new to Lisp, I have a feeling that most of the answers that
have been posted are going way over your head, so I'm going to try a
simpler answer. Because I'm simplifying, I don't expect to address all
details, and I hope the pedants in the group won't waste time correcting me
because I've glossed over something.

In Lisp, most expressions are ordinary function calls, in which all the
argument expressions are evaluated automatically, and their resulting
values passed to a function.

But sometimes you need to delay evaluating an expression. The classical
example, which I used in another post in this thread, is IF: it should only
evaluate one of the consequent expressions, and which one to evaluate is
determined by the test expression.

One way to defer evaluation is by defining a function whose body is the
expression; it won't be evaluated until the function is called. Functions
defined on the fly like this are traditionally called "thunks", and LAMBDA
is the way we define them in Lisp. I showed an example of this technique
in my other post as IF-FUNCTION.

Another way to delay argument evaluation is with a macro. When a macro is
invoked, the arguments are not automatically evaluated. The macro receives
the parameter expressions as is, and it can rewrite the entire expression
into a new expression that will be evaluated in its place. This rewrite
could make use of special operators that evaluate expressions in special
ways. This was demonstrated in my other post as IF-MACRO; it expands into
a use of COND, which is a more primitive conditional that defers
evaluation. But perhaps a better version of that, to relate it to the
LAMBDA example, would be:

(defmacro if-macro (test then-exp else-exp)
`(if-function ,test
(lambda () ,then-exp)
(lambda () ,else-exp)))

Macros tend to be the preferred way of doing these types of things mainly
because it allows more terse code. If we did all these things using
functions, we would have (lambda () ...) littered all over the place.

There are languages where this *is* the normal way of doing things; an
examples is Smalltalk. What you'll notice is that it has a more concise
syntax for defining anonymous functions; IIRC, it's [<body>]. This was
intentionally done to look similar to the way Algol-style languages use
{<body>} or BEGIN <body> END to group bodies of functions, loops, and
conditionals. Many programmers in languages like this probably don't even
realize they're passing around thunks because of this (and the compilers
can often optimize the explicit function calls away).

ilias

unread,
Sep 27, 2002, 2:22:34 PM9/27/02
to
Jacek Podkanski wrote:
> Hi,
>
> I'm quite new to Lisp.

i'm a lisp novice, too

> At the moment I'm trying to understand some of its
> concepts.

take care of the documentation. it sometimes fuzzy and overloaded with
confusing terminology.

> Somewhere I seen information that everything that can be done
> with macros can be done with lambdas.

was this a scheme-lover?

> Is this correct?

this seems to be correct.

but correct is, that macros an lambdas are both for the... garbage.

cause i can do everything what they do with a few RISC Assembler Op-Codes.

> Can anybody point
> out differences between the two?

macros are something like code generators.

you can generate new code whilst running a lisp programm.

this is very funny and powerfull.

the look like functions.

this is very pretty.

-

lambdas are something very easy but *very* complicated described.

you can imagine them as functions.

functions without a declaration.

in-place-function-code.

manybe some people like to kill me now, but this small essence i've
understood.

and i think it's not wrong.

and i think you understand this, too.

-

soon i will assimilate lambdas.

this is important to me.

for an "historical research" i'd like to do.

when i've done that, i'll explain them 'with apples'.

this means: very easy, understandable for nearly everyone.

Translucency.

then you'll see how easy they are.

but maybe you understand prior to my finishing.

-


>
> Regards

Jacek Podkanski

unread,
Sep 27, 2002, 2:52:15 PM9/27/02
to
ilias wrote:

> Jacek Podkanski wrote:
>> Hi,
>>
>> I'm quite new to Lisp.
>
> i'm a lisp novice, too
>
>> At the moment I'm trying to understand some of its
>> concepts.
>
> take care of the documentation. it sometimes fuzzy and overloaded with
> confusing terminology.

Depends what you read. The things I read are suprisinly easy to understand.


>
>> Somewhere I seen information that everything that can be done
>> with macros can be done with lambdas.
>
> was this a scheme-lover?

python lover probably.

>
>> Is this correct?
>
> this seems to be correct.

I was told it's incorrect, and I regret it because i could try out some
Lisp concepts in my favourite scripting language, that is Ruby.


>
> but correct is, that macros an lambdas are both for the... garbage.
>
> cause i can do everything what they do with a few RISC Assembler Op-Codes.

I f language I use doesn't have direct access to assemler I need at least
lambdas.

--
Jacek Podkanski

Kenny Tilton

unread,
Sep 27, 2002, 2:54:52 PM9/27/02
to

ilias wrote:
> macros are something like code generators.

Quite.

> you can generate new code whilst running a lisp programm.

Not quite.

In the ACL debug window:

(defmacro mdbl (n) (print "mdbl at work!") `(+ ,n ,n))
MDBL

(mdbl 2)
"mdbl at work!"
4

The ACL interpreter has to kick off the mdbl macro function to do
the interpretation, so it may seem as if code is normally generated
while my program is running. But...

Now I compile this in an ACL editor window:

(defun use-mdbl (n) (mdbl n))

And see this in the debug window, where the print output (and the result
of the incremental compilation) goes:

"mdbl at work!"
USE-MDBL

ie, the new code is generated at compile-time. Now back in the debug window:

> (use-mdbl 2)
4

Observe that the macro does not run/generate new code at this point.

> this is very funny and powerfull.

quite.

k,c


Jacek Podkanski

unread,
Sep 27, 2002, 3:21:12 PM9/27/02
to
Tim Bradshaw wrote:

<snip>

> So if you didn't have macros, you could implement them - the really

You intrigued me a lot with this. It makes me wonder if I could do it in
another language.

> crucial thing is READ, and source code being data. Indeed this is
> almost certainly how the first Lisp macro systems *were* written.
>
> But just because you *could* do it doesn't mean you should *want* to,
> of course.
>
> --tim

--
Jacek Podkanski

Thomas F. Burdick

unread,
Sep 27, 2002, 3:31:15 PM9/27/02
to
Jacek Podkanski <jacekpo...@supanet.com> writes:

> Tim Bradshaw wrote:
>
> <snip>
>
> > So if you didn't have macros, you could implement them - the really
>
> You intrigued me a lot with this. It makes me wonder if I could do it in
> another language.

Probably, *but* ... what other language has something like READ? The
important thing is to get a fairly-easy-to-manipulate structured
representation of the source. It helps if it's trivial to mentally
convert between the textual and structural representations.

--
/|_ .-----------------------.
,' .\ / | No to Imperialist war |
,--' _,' | Wage class war! |
/ / `-----------------------'
( -. |
| ) |
(`-. '--.)
`. )----'

Stephen J. Bevan

unread,
Sep 27, 2002, 3:35:22 PM9/27/02
to
k...@ashi.footprints.net (Kaz Kylheku) writes:
> We had a higher-order-functions versus macros debate here recently,
> and eventually the higher-order-functions proponents ran out of
> arguments supporting the thesis that HOF's can replace macros.

Did someone in that thread put forward that thesis? The closest I can
see is the suggestion that HOFs can be used to produce something that
is visually similar to certain (definitely not all) uses of macros
For example, if, while, with-x, ... etc. could all be done with HOF's
and in some languages they are e.g. Smalltalk. Other types of macro,
such as defstruct, could not be done with HOFs. Using macros for the
former is a matter of taste since one could use HOFs if one so
desired. Using macros for the latter is not, one either uses macros
or one has to do without the desired abstraction completely.

Barry Margolin

unread,
Sep 27, 2002, 4:27:10 PM9/27/02
to
In article <m3znu39...@dino.dnsalias.com>,

Stephen J. Bevan <ste...@dino.dnsalias.com> wrote:
>k...@ashi.footprints.net (Kaz Kylheku) writes:
>> We had a higher-order-functions versus macros debate here recently,
>> and eventually the higher-order-functions proponents ran out of
>> arguments supporting the thesis that HOF's can replace macros.
>
>Did someone in that thread put forward that thesis? The closest I can
>see is the suggestion that HOFs can be used to produce something that
>is visually similar to certain (definitely not all) uses of macros
>For example, if, while, with-x, ... etc. could all be done with HOF's
>and in some languages they are e.g. Smalltalk. Other types of macro,
>such as defstruct, could not be done with HOFs.

Here's a simple (untested) HOF version of DEFSTRUCT:

(defun create-structure (name &rest fields)
(let ((field-count (length fields))
(field-keywords (mapcar (lambda (f)
(intern (symbol-name f) "KEYWORD"))
fields)))
(setf (symbol-function (intern (format nil "MAKE-%A" name)))
(lambda (&rest args)
(let ((struct (make-array field-count)))
(loop for i upfrom 0
for k in field-keywords
do (setf (aref struct i) (getf args k)))
struct)))
(loop for i upfrom 0
for f in fields
do (let ((i i) ; ensure new lexical binding for closure
(accessor (intern (format nil "%A-%A" name f))))
(setf (fdefinition accessor)
(lambda (struct) (aref struct i)))
(setf (fdefinition `(setf ,accessor))
(lambda (new-val struct) (setf (aref struct i) new-val)))))))

(defstruct foo a b c)

becomes

(create-structure 'foo 'a 'b 'c)

Joe Marshall

unread,
Sep 27, 2002, 4:41:31 PM9/27/02
to
Barry Margolin <bar...@genuity.net> writes:

Er, um, yeah, but.....

Your non-macro version of DEFSTRUCT is using reflection operators like
INTERN and (SETF FDEFINITION) to do a sort of `mini' EVAL. So rather
than return a form as a result of a macro expansion, this is
performing the effect of EVALing what would have been returned.

It certainly solves the problem, but I think it violates the spirit.

Barry Margolin

unread,
Sep 27, 2002, 5:34:23 PM9/27/02
to
In article <vg4rxj...@ccs.neu.edu>, Joe Marshall <j...@ccs.neu.edu> wrote:
>Er, um, yeah, but.....
>
>Your non-macro version of DEFSTRUCT is using reflection operators like
>INTERN and (SETF FDEFINITION) to do a sort of `mini' EVAL. So rather
>than return a form as a result of a macro expansion, this is
>performing the effect of EVALing what would have been returned.
>
>It certainly solves the problem, but I think it violates the spirit.

It's only doing this to give the functions global names. Here's a version
that simply returns the functions, and leaves it up to the caller to keep
track of them in whatever way it wants:

(defun create-structure (name &rest fields)
(let ((field-count (length fields))
(field-keywords (mapcar (lambda (f)
(intern (symbol-name f) "KEYWORD"))
fields)))

(let ((maker


(lambda (&rest args)
(let ((struct (make-array field-count)))
(loop for i upfrom 0
for k in field-keywords
do (setf (aref struct i) (getf args k)))
struct)))

(getters


(loop for i upfrom 0
for f in fields

collect (let ((i i) ; ensure new lexical binding for closure


(accessor (intern (format nil "%A-%A" name f))))

(lambda (struct) (aref struct i))))
(setters


(loop for i upfrom 0
for f in fields

collect (let ((i i) ; ensure new lexical binding for closure


(accessor (intern (format nil "%A-%A" name f))))

(lambda (new-val struct) (setf (aref struct i) new-val)))))))

(values maker getters setters))))

But if you don't give these functions global names, what's the point of
defining structures in the first place? And isn't one of the benefits of
having reflection functions that you can do things like this *without*
having to use macros?

Contrast it with a language like C, where the only way to define structures
in any kind of automated way is with macros; Lisp provides you with
functional reflection that allows you to do this stuff on the fly.

Rather than thinking of my previous solution as a "mini-EVAL", I prefer to
think of it the opposite way: EVAL is often a crutch that needs to be used
when there's no functional way to accomplish what you want. E.g. if we
couldn't do SETF of FDEFINITION, I'd have to cons up a DEFUN form and EVAL
it.

Stephen J. Bevan

unread,
Sep 27, 2002, 7:39:33 PM9/27/02
to
Barry Margolin <bar...@genuity.net> writes:
> >Did someone in that thread put forward that thesis? The closest I can
> >see is the suggestion that HOFs can be used to produce something that
> >is visually similar to certain (definitely not all) uses of macros
> >For example, if, while, with-x, ... etc. could all be done with HOF's
> >and in some languages they are e.g. Smalltalk. Other types of macro,
> >such as defstruct, could not be done with HOFs.
>
> Here's a simple (untested) HOF version of DEFSTRUCT:
>
> [snipped an example that uses reflective capabilities]

When I wrote the above I was thinking about the languages in which
most of the examples of HOFs had been given, in particular O'Caml and
SML. O'Caml doesn't have reflective capabilities and SML doesn't have
in the standard though certain implementations do. As you note, using
them one does not have to use macros and that is effectively the route
that Smalltalk goes in. For example, the following taken from GNU
Smalltalk defines the class RegularExpression and so is similar in
spirit to a call to defstruct :-

Object subclass: #RegularExpression
instanceVariableNames: 'selectors params noDollar string'
classVariableNames: 'Debug'
poolDictionaries: ''
category: 'Examples-Useful'!

Jacek Podkanski

unread,
Sep 27, 2002, 3:11:49 PM9/27/02
to
Erik Naggum wrote:

> * Jacek Podkanski
> | I'm quite new to Lisp.
>
> Welcome!
>
> | At the moment I'm trying to understand some of its concepts.
>
> Commendable to understand first and judge later. Disturbingly many
> judge first and therefore never understand.
>
> | Somewhere I seen information that everything that can be done with
> | macros
> | can be done with lambdas. Is this correct?
>
> It is an arbitrary statement devoid of contents and meaning, so
> therefore neither correct nor incorrect.

I thought that someone would know anyway. Someone replied to me:
"the whole point of macros is that they let you do things that *cannot* be
done with functions". I think he is right, please correct me if I'm wrong.


>
> | Can anybody point out differences between the two?
>
> Yes, but it would be meaningless to you until you are experienced with
> Lisp.

Please do not get me wrong. I do not want to start any Word War II, but
it's a bit like catch 22.

* It is meaningless until you are experienced,
* you can't get experience as long as things are meaningles

I think this is what has upset ilias.

But I don't care. I hope i will find way round this problem.

>
> Forget the statement entirely and proceed to learn Lisp as if you had
> never

I will do it.

> heard it. You will be much better off than prematurely trying to attach
> meaning to this statement.
>

I thought I understood it before I saw this statement about lambdas and
macros, I wanted to make sure I understand it right.
--
Jacek Podkanski

Alain Picard

unread,
Sep 27, 2002, 9:17:19 PM9/27/02
to
Jacek Podkanski <jacekpo...@supanet.com> writes:

> I thought that someone would know anyway. Someone replied to me:
> "the whole point of macros is that they let you do things that *cannot* be
> done with functions". I think he is right, please correct me if I'm wrong.

This is a different statement than your original one, and is true.
The thing you can do with macros that you _cannot_ do with functions
is control the evaluation of the arguments.

Erik Naggum

unread,
Sep 27, 2002, 11:22:30 PM9/27/02
to
* Jacek Podkanski

| I thought that someone would know anyway. Someone replied to me:
| "the whole point of macros is that they let you do things that *cannot* be
| done with functions". I think he is right, please correct me if I'm wrong.

Sorry, but this is a game that I will simply refuse to play. You appear to
believe that other people can determine exactly what you mean by vague
statements and "correct" you if you are "wrong", but they have no idea what
you interpret these statements to mean (i.e., which consequences they have
for your thinking and understanding), what you would need to be told to see
something a different way, or where you went wrong, such that you could be
corrected in an efficient and productive way.

| Please do not get me wrong. I do not want to start any Word War II, but it's
| a bit like catch 22.

Whenever you see a Catch-22-like situation, you must realize that such
situations do not actually exist and that you have become satisfied with
their existence because you believe they may exist. Your whole philosophical
take on understanding the world around you is broken if you get into a Catch
22 situation. Zoom out, and you see the circularity that confused you and
how feedback loops actually have other inputs, too.

| * It is meaningless until you are experienced,
| * you can't get experience as long as things are meaningles

This is so stupid there is no point in trying to help you.

| I thought I understood it before I saw this statement about lambdas and
| macros, I wanted to make sure I understand it right.

Like so many other people who have trouble understand something, you appear
to believe in acontextual knowledge and acontextual acquisition of same.
There is no way you can resolve this problem except to understand how all
knowledge is contextual and its acquisition is also contextual. Random bits
of knowledge that are not properly connected will work for quite a while
because the human brain is fortunately so wired that it makes both context
and connections implicit until you reach a certain level of abstractness of
the things you want to learn and cope with. When you cease to learn by
doing, which contrary to popular belief is the single most inefficient way to
learn anything, but can learn from understanding, which takes much learning
by doing to become possible, your connections and contexts need to be made
explicit and you need to think in terms of them. You appear to be in some
sort of in-between position where you just need to sit down with yourself and
study how you know what you know and learn what you learn.

Eagerness is good, but so is letting things come to you in a timely manner.

JB

unread,
Sep 28, 2002, 6:30:03 AM9/28/02
to
Jacek Podkanski wrote:

> I thought that someone would know anyway. Someone replied
> to me: "the whole point of macros is that they let you do
> things that *cannot* be done with functions". I think he
> is right, please correct me if I'm wrong.

Eric is of course right but he has his own way of expressing
things, so the first thing is that you do not mind.
Your statement is so vague that you do not gain anything by
getting any answer.
So the best way is to write some functions and to write some
macros and *then* you will see. And when you have technical
questions concerning this, you can ask those strictly
technical questions. (Of course you can ask any questions.)

To judge from your posting you are a newbie to programming
as macros pop up in other languages too, for example in C.
Basicaly C macros and Lisp macros are the same, though
Lisp's macros are much more powerful. (Again, this
statement is a bit stupid as it is too vague.) So I
conclude that you have not come across C macros either.

There are some excellent online tutorials on how to program
Lisp and you should consult those.

--
Janos Blazi


-----------== Posted via Newsfeed.Com - Uncensored Usenet News ==----------
http://www.newsfeed.com The #1 Newsgroup Service in the World!
-----= Over 100,000 Newsgroups - Unlimited Fast Downloads - 19 Servers =-----

ilias

unread,
Sep 28, 2002, 9:25:34 AM9/28/02
to
Jacek Podkanski wrote:
> ilias wrote:
>
>
>>Jacek Podkanski wrote:
>>
>>>Hi,
>>>
>>>I'm quite new to Lisp.
>>
>>i'm a lisp novice, too
>>
>>
>>>At the moment I'm trying to understand some of its
>>>concepts.
>>
>>take care of the documentation. it sometimes fuzzy and overloaded with
>>confusing terminology.
>
> Depends what you read. The things I read are suprisinly easy to understand.

seems we agree.

i said: "sometimes".

you said: "depends what you read".

this is compatible.

which things did you read?

>
>>>Somewhere I seen information that everything that can be done
>>>with macros can be done with lambdas.
>>
>>was this a scheme-lover?
>
> python lover probably.

aha.

python has this magic 'lambdas', too.

>
>
>>>Is this correct?
>>
>>this seems to be correct.
>
>
> I was told it's incorrect, and I regret it because i could try out some
> Lisp concepts in my favourite scripting language, that is Ruby.

i see.

>
>>but correct is, that macros an lambdas are both for the... garbage.
>>
>>cause i can do everything what they do with a few RISC Assembler Op-Codes.
>
> I f language I use doesn't have direct access to assemler I need at least
> lambdas.

now i'm confused.

and very curious.

>
>>>Can anybody point
>>>out differences between the two?

[...]

Jens Axel Søgaard

unread,
Sep 28, 2002, 10:24:43 AM9/28/02
to
ilias wrote:
> python has this magic 'lambdas', too.

All that glitters is not gold.

http://p-nand-q.com/lambda.htm

--
Jens Axel Søgaard

Tim Bradshaw

unread,
Sep 28, 2002, 11:00:21 AM9/28/02
to
* Jacek Podkanski wrote:

> You intrigued me a lot with this. It makes me wonder if I could do it in
> another language.

Well, you could - you can do anything in any language that you can in
another. But how hard it is might influence your decision. A few
things make Lisp very well suited to it:

1. Source code is data. The structure of the source of a Lisp program
is available to Lisp as a data structure. This isn't true for many
languages: there clearly *is* some data structure that is built
from the source text, but what it is is an internal detail of the
compiler - the syntax of the language is specified in terms of
character strings instead of some richer structure.

2. Very low commitment data structure for source code. For years I
thought that if Lisp was done `right' nowadays instead of using
lists and symbols &c for the source code and relying on whatever
processes the code (such as macros) to do a lot of work, one would
want to have some much `better' structure - so the parser would
give you objects like blocks or definitions which would have a lot
of information already worked out about them. But in 1998 or so I
suddenly had a blinding insight that this would be a huge mistake:
it's precisely *because* the structure of Lisp source is rather
simple that macros are so powerful. Because the parser has not
made all sorts of decisions for you about what it has seen, you are
free to make your own decisions and implement your own kinds of
structures. It is more work in the simplest case, but it makes
complicated things - like defining your own language with
constructs that don't exist in the underlying system - far easier.

3. Regular semantics. In languages like C, for instance there are
expressions and statements, and they are different, and not
substitutable for each other. In Lisp there are just expressions,
and you can bundle up any number of expressions into a single
expression with PROGN or its kin. This kind of simplicity - there
are less contexts in Lisp - makes it very easy to write
code-transformation programs - macros in other words.

--tim

ilias

unread,
Sep 28, 2002, 1:47:18 PM9/28/02
to
Kenny Tilton wrote:
>
>
> ilias wrote:
>
>> macros are something like code generators.
>
> Quite.
ok. [something like / quite]

>
>> you can generate new code whilst running a lisp programm.
>
>
> Not quite.

aha

>
> In the ACL debug window:
>
> (defmacro mdbl (n) (print "mdbl at work!") `(+ ,n ,n))
> MDBL
>
> (mdbl 2)
> "mdbl at work!"
> 4
>
> The ACL interpreter has to kick off the mdbl macro function to do
> the interpretation, so it may seem as if code is normally generated
> while my program is running. But...
>
> Now I compile this in an ACL editor window:
>
> (defun use-mdbl (n) (mdbl n))
>
> And see this in the debug window, where the print output (and the result
> of the incremental compilation) goes:
>
> "mdbl at work!"
> USE-MDBL
>
> ie, the new code is generated at compile-time. Now back in the debug
> window:
>
> > (use-mdbl 2)
> 4
>
> Observe that the macro does not run/generate new code at this point.

so macros *can be* something like codegenerators,

but can be 'missused' as simple non-generating 'functions', too.

ok

>
>> this is very funny and powerfull.
>
> quite.

ok

>
> k,c
>
>

Lieven Marchand

unread,
Sep 28, 2002, 8:21:04 AM9/28/02
to
Alain Picard <apicard+die...@optushome.com.au> writes:

> The thing you can do with macros that you _cannot_ do with functions
> is control the evaluation of the arguments.

This is true in the context of Common Lisp, but perhaps not in the
wider context the OP was asking about.

There have been Lisp dialects where you could control the evaluation
of arguments like this

(DEFINE QUOTE-REVERSE FEXPR (ARGS)
(REVERSE ARGS))

where the FEXPR indicates to the system not to evaluate the arguments,
or even with more fine grained control

(DEFINE F (X &QUOTE Y) ...)

where X would be evaluated and Y not.

Even in these dialects there are differences between functions and
macros. It would be possible to implement LOOP as a FEXPR function,
but this would force parsing and interpreting of the LOOP form at each
invocation. In contrast a macro implementation does that work once. On
the other hand an FEXPR function can use the local environment.

--
Hai koe, zei de stier,
Kom mee met mij in de wei,
Dan zijn we tweezaam.
Lieven Marchand <m...@wyrd.be>

Gareth McCaughan

unread,
Sep 28, 2002, 6:10:53 PM9/28/02
to
Jacek Podkanski wrote:

> > | Somewhere I seen information that everything that can be done with
> > | macros
> > | can be done with lambdas. Is this correct?
> >
> > It is an arbitrary statement devoid of contents and meaning, so
> > therefore neither correct nor incorrect.
>
> I thought that someone would know anyway. Someone replied to me:
> "the whole point of macros is that they let you do things that *cannot* be
> done with functions". I think he is right, please correct me if I'm wrong.

1. Anything you can do with macros, you can do with functions.

For instance, with functions you can write your own Lisp
interpreter or compiler which implements macros, and then
use that.

For instance, a lot of the things you do with macros could
instead be done (at the cost of repeated code and syntactic
inconvenience) by packaging up the lumps of code that the
macro would work on inside closures and feeding those to
ordinary functions.

2. Macros are for doing things that can't be done with functions.

For instance, extending the syntax of your language without
having to reimplement the whole thing.

For instance, expressing operations that manipulate lumps of
code without needing lots of syntactic noise.

I suspect that whoever told you "everything that can be done
with macros can be done with lambdas" meant the second of
the for-instances under #1 above, in which case "everything"
goes way too far: macros can do things that go way beyond
just deciding which arguments to evaluate when. In other
words, with the meaning I think they intended, the statement
is wrong. But it's hard to be sure because there's so much
ambiguity in it.

The people who've said you won't really understand what's
going on here without diving in and learning some more
are probably correct, by the way.

--
Gareth McCaughan Gareth.M...@pobox.com
.sig under construc

Jacek Podkanski

unread,
Sep 28, 2002, 10:11:15 PM9/28/02
to
Gareth McCaughan wrote:

I agree with you.
--
Jacek Podkanski

Jacek Podkanski

unread,
Sep 28, 2002, 6:14:34 PM9/28/02
to
Erik Naggum wrote:

Dear Sir,

Perhaps you are an expert with years of experience, but I am not. I realise
I ask daft questions and this one probably isn't last. You might feel upset
that someone asked such obvious question. Tell me haw many years ago last
time you asked a question which could be daft to an expert. Even if it was
ages ago you had to start somewhere.

It reminds me of situation with Linux. Some people complain that when you
ask a question you get reply RTFM, which means Read The ******* Manual. Now
I write this message on a Linux box, so I got there, I hope to do the same
with Lisp. It's just easier sometimes to get an answer from a human than
looking for it through the books.

--
Jacek Podkanski

Erik Naggum

unread,
Sep 29, 2002, 1:31:31 AM9/29/02
to
* Jacek Podkanski

| Perhaps you are an expert with years of experience, but I am not. I realise
| I ask daft questions and this one probably isn't last. You might feel upset
| that someone asked such obvious question.

It is not your "daft" questions that bother me, it is that you put people who
answer you in an impossible situation. You ask people to confirm that you
are right or correct you if you are wrong. This is actually unworkable. It
may work for trivial questions of fact, but philosophical-like questions
cannot be dealt with that way. And programming languages carry philosophies
that you need to grasp before you grasp the programming language.

| Tell me haw many years ago last time you asked a question which could be
| daft to an expert. Even if it was ages ago you had to start somewhere.

Here you assume that everybody else is just like you. This is just not the
case. Until you realize that you have a counter-producitve approch to the
whole knowledge-acquisition process, you will not really figure anything out,
but you will /think/ you do. The desire you exhibit to be /correct/ is the
only thing that is really "daft" here. Things are not "correct". When you
are in the learning phase, things have a different meaning than when you are
more experienced. Concepts are usually disconnected when you new to a field
and sentences change meaning as you connect the underlying concepts.

I have always been humble towards knowledge I do not have, of systems I do
not know, of philosophies that I do not know. What makes it able to learn
very quickly is that I listen to what experienced people say and ask them the
questions that will help me connect things. My goal is understand as deeply
as possible what is going on around me. I have no use for sentences whose
meaning I do not know, but which other people say is "correct". If I base my
reasoning on a misunderstanding of a "correct" statement, I shall have very
significant problem clearing this up. When asked, the likelihood that I will
repeat a "correct" statement, but meaning something other than other people
interpret it to mean, is very significant. Many people have found themselves
flunked after believing misunderstandings of "correct" statements. Back when
I helped fellow students, this was in fact /the/ most significant cause of
their problems. More often than not, they could repeat textbook statements
flawlessly, but made the oddest reasoning from them. I discovered that in
the teaching position, the largest problem is to discover the last point at
which the student had actually understood things, such you coul revert to
that position and fix the first mistake out of that state. Many students are
unable to think clearly and therefore muddle through a mess of guesswork and
random connections, where they are unprepared for the scrutiy of their
thinking that debugging it necessarily entails. The largest problem I have
seen in my own and fellow students was been a lack of thinking skills. Most
people are simply unskilled at thinking and have "succeeded" with fairly
idiotic ersatz devices until they really have to grapple with abstract ideas
and then feel stupid even though they are quite intelligent by nature (so
they have managed to keep their lack of thinking skills a secret from both
themselves and others). Now, depending on whether their self-esteem is based
in the belief that their intelligence is under attack if they make stupid
mistakes or whether it is based in the certainty that they are intelligent
enough to get out of any situation they might wittingly or unwittingly get
themselves into. Those who believe their intelligence cannot be as high as
they had hoped if they make stupid mistakes generally tend to have brittle
egoes and therefore incorrigible and just continue on their erroneous path
and eventually arrive someplace useful, from where they will announce loudly
that they were never wrong to begin with. This personality trait tends to
waste enormous amounts of effort in protecting their brittle self-esteem.
The other kind, who trust their intelligence to get them through anything,
will react to a realization that they made a stupid mistake with an apology,
almost, and then work hard to correct it. All their energy goes into making
sure they get things as right as possible, but no obsessive compulsions about
being correct at any time. More than anything else, methological differences
like this predict future ability to deal with the unexpected and unknown. If
you believe you have to /be/ correct, you will make many mistakes. If you
believe you can always /become/ correct, you will be correct most of the time.

Just because you are a novice does not mean that you ask "daft" questions.
You do not have to be an expert to realize that "correct me if I'm wrong" is
a recipe for grave mistakes and serious confusion down the line.

Just over three weeks ago, I wrote a scathing review of a manuscript on the
Semantic Web, after having spent another three weeks with that manuscript.
Then I visited my local library and talked with their staff and learned that
the 5th edition of the Norwegian adaption of the Dewey Decimal Classification
was just around the corner. I acquired the books and got all excited about
the ability to use this enormous and ongoing work for managing the "ontology"
of the Semantic Web. I have since then been communicating with almost 50
people in national libraries in Norway, England, Germany, and the U.S., and
several large public libraries in Norway. According to some, I have come up
to speed in two weeks compared with the two years fresh college students in
information and library science require to understand the same isuses. This
is not because I am old and very experienced and have always learned quickly,
but because I /listen/ to people who more than I do and because I am willing
to put in 16 hours a day to learn something from the best available sources.
Keep learning new things by spending two hours studying something you have no
immediate use for as a daily routine for three decades, and you just know a
lot and can connect a lot more dots than if you only learn while "forced" to
by teachers and exams and the like. Add good methodology and things come
real easy after a while. With no "daft" questions in sight. Avoiding stupid
questions is /not/ intractable, just ask intelligent questions, meaning those
whose answers actually mean something to you personally and actually help you
understand something at your current level of expertise.

Some say there are no stupid questions, but this is a lie. A stupid question
is a question to which the answer would not benefit the questioner.

| It's just easier sometimes to get an answer from a human than looking
| for it through the books.

Books give you the clear advantage that you learn at your own pace. The
books were written by people who were trained in presenting the material in a
pedagogical manner, their manuscripts went through several drafts, and the
people who reviewed it have slaughtered parts of it and encouraged other
parts. A book is an immense cooperative project. Any given individual you
ask will require a personal rapport with your prior understanding before he
can provide you with useful and contextually relevant and correct answers.
You need to be aware of this process when you ask questions and receive
answers to them.

--
Erik Naggum, Oslo, Norway Today, the sum total of the money I
would retain from the offers in the
more than 7500 Nigerian 419 scam letters received in the past 33 months would
have exceeded USD 100,000,000,000. You can stop sending me more offers, now.

Rob Warnock

unread,
Sep 29, 2002, 6:10:15 AM9/29/02
to
Erik Naggum <er...@naggum.no> replied:
+---------------

| Any given individual you ask will require a personal rapport with
| your prior understanding before he can provide you with useful and
| contextually relevant and correct answers. You need to be aware of
| this process when you ask questions and receive answers to them.
+---------------

Amen! In fact, this is *so* true that for the last several years I
have made it an absolute requirement that before agreeing to assist
someone on a project via email that we have at least one lengthy
face-to-face meeting -- or if that is not possible (e.g., the person is
in a distant country) at the *very* least a lengthy telephone call --
during which we mutually introduce ourselves, go into some considerable
detail on our backgrounds, technical histories, skills, technical
preferences/prejudices (e.g., we {love,hate} {C,C++,Perl,PHP,Lisp,etc.}),
so that we have enough (or at least a bare minimum of) context about
each other to be able to at least ask the right *questions*!!

With such an intro, the subsequent email exchanges tend to be crisp,
to the point, and fruitful. (Though every so often, another, much-shorter
phone call my be required to "get back in sync".)

But without such a mutual "core dump" intro, almost invariably *enormous*
amounts of time get wasted in an increasingly lengthy and frustrating
series of email exchanges as we attempt resolve a growing cloud of
confusion and misunderstanding and try to hammer out some common ground
for cooperation.

Now how does one apply that to coming to a new newsgroup? It doesn't
seem to offer any hope! Well, actually, it does, though the process
just takes a *lot* longer. Instead of single dinner meeting or one
several-hour phone call, when coming to a newsgroup new to you
(technical or not), for the first several weeks (yes, I said *weeks*!),
just "lurk" -- that is, only read what others write; don't post anything
of your own.

First, you will almost surely find the answers to most of your initial
questions (e.g., "Is there an FAQ for this group?", "Are there some
resource web sites?"), but much more importantly, you will (1) learn
the style of interaction which is practiced in that group, and (2) learn
who the main players are, and who generally gives good advice (or at
least well-reasoned answers) and who just flames & trolls.

But you also need to go *read* the various off-newsgroup references
you see mentioned -- for comp.lang.lisp, that means exploring most of
<URL:http://www.lisp.org/> for starters, as well learning how to use
<URL:http://www.lispworks.com/reference/HyperSpec/Front/index.htm>.

Then, and only then, you might (actually, probably *will*) have enough
context to pose "reasonable" newbie questions...


-Rob

-----
Rob Warnock, PP-ASEL-IA <rp...@rpw3.org>
627 26th Avenue <URL:http://www.rpw3.org/>
San Mateo, CA 94403 (650)572-2607

ilias

unread,
Sep 29, 2002, 9:24:16 AM9/29/02
to
Jacek Podkanski wrote:
> Erik Naggum wrote:
[...]


> Dear Sir,
>
> Perhaps you are an expert with years of experience, but I am not. I realise
> I ask daft questions and this one probably isn't last. You might feel upset
> that someone asked such obvious question. Tell me haw many years ago last
> time you asked a question which could be daft to an expert. Even if it was
> ages ago you had to start somewhere.
>
> It reminds me of situation with Linux. Some people complain that when you
> ask a question you get reply RTFM, which means Read The ******* Manual. Now
> I write this message on a Linux box, so I got there, I hope to do the same
> with Lisp. It's just easier sometimes to get an answer from a human than
> looking for it through the books.
>

Jacek,

don't take his words to serious.

I think nobody who knows him does that. He has something like a
'diplomatic immunity' in this forum.

The adressed person, the "immune", is high-intelligent.

But somehow the soul of the "immune high-intellingent" has been filled
with bitterness. You can read this in his words. Read carefully a few posts.

The "immune high-intelligent bitter" becames often due to his biterrness
irrational. High intelligence is not a guarantee for high-rationality
(in context of calm, of where to apply the high-intelligence).

I don't think that the "immune high-intelligent bitter irrational" takes
his endless babbling serious. Endless babbling about information the
posters (e.g. you) haven't requested.

Even if this babbling of the "immune high-intelligent bitterly
irrational babbler" has an essence, the posters are in general not
willing to switch into the condition "deep, philosophy, recognition,
reflection".

The posters have a small simple problem and they want a small simple
solution or discussion. They are in the condition "small problem,
discuss". And in general *they* decide when they are in the condition to
deal with "deep, philosophy, recognition, reflection" - a big complex
problem.

Forcing someone into this condition (especially without answering to the
main problem) is very ungentle and serves primary (if not only) personal
needs. This behaviour is very egoistic.

Maybe the "immune high-intelligent bitterly irrational egoistic babbler"
doesn't take himself serious and sees the posters in this forum as his
personal puppets.

I've identified many puppets (or sheeps) - Will you become one of them?

You can simply ignore the posts of the "immune high-intelligent bitter
irrational egoistic babbling puppeteer", who does not respect the
individuality of a human being.

From the replies in the group you see: there are many people that are
kindly enouth to simply answer to your question in the way they've
understood your question.

And maybe they discuss *carefully* and with *respect* your personal
process-model of learning, *after* they have respectfully handled your
request.

Enjoy your very personal process of learning.

It is better than *any* "personal perfect process" that an

"immune high-intelligent bitter irrational egoistic disrespectful
babbling puppeteer"

suggests.

-

puppeteer.

weapon.

you.

strongest.

mine.

-

limits.

-

Fred Gilham

unread,
Sep 29, 2002, 12:00:59 PM9/29/02
to

> I think nobody who knows him does that. He has something like a
> 'diplomatic immunity' in this forum.

You are mistaken.

Erik does not have diplomatic immunity.

Erik is one of the few people in any forum whose messages I actually
save for later perusal.

snapdragon:~ > locate naggum | grep -v -c hyperspec
15

There are a couple people whom I wish he could tolerate better
(because I enjoy hearing their input as well). On the other hand,
there are a few people whose flame-job I think needs touching up[1]
that he has chosen to avoid addressing. :-)

I ran across a quotation that I don't have the attribution for but I
really like:

Perhaps the greatest damage the American system of education has
done to its children is to teach them that their opinions are
relevant simply because they are their opinions.

I've come to think this is not just the American system of education.
It seems to be a global problem. I think people can say what they
want, that's their right. But there is no `right to be heard'. Being
heard must be earned. Many people don't realize that there's a
difference.

[1] Cf. "Deal of the Century" w/Chevy Chase, Sigourney Weaver
--
Fred Gilham gil...@csl.sri.com
The vicissitudes of history, however, have not dissuaded them from
their earnest search for a "third way" between socialism and
capitalism, namely socialism. --- Fr. Richard John Neuhaus

ilias

unread,
Sep 29, 2002, 1:08:41 PM9/29/02
to
Fred Gilham wrote:
>>I think nobody who knows him does that. He has something like a
>>'diplomatic immunity' in this forum.
>
>
> You are mistaken.

of course, 'Mr. puppet'.

>
> Erik does not have diplomatic immunity.

i've said: 'diplomatic immunity'

>
> Erik is one of the few people in any forum whose messages I actually
> save for later perusal.
>
> snapdragon:~ > locate naggum | grep -v -c hyperspec
> 15

whow.

>
> There are a couple people whom I wish he could tolerate better
> (because I enjoy hearing their input as well).

hear, hear.

> On the other hand,
> there are a few people whose flame-job I think needs touching up[1]
> that he has chosen to avoid addressing. :-)

cannot decipher this. [1]

>
> I ran across a quotation that I don't have the attribution for but I
> really like:
>
> Perhaps the greatest damage the American system of education has
> done to its children is to teach them that their opinions are
> relevant simply because they are their opinions.
>
> I've come to think this is not just the American system of education.

let me guess: Norwegian, too.

> It seems to be a global problem. I think people can say what they
> want, that's their right. But there is no `right to be heard'. Being
> heard must be earned. Many people don't realize that there's a
> difference.

i'll answer you with the words of the "immune high-intelligent bitter
irrational egoistic disrespectful babbling puppeteer", which you may
understand better:

bullshit!

Fred Gilham

unread,
Sep 29, 2002, 1:52:25 PM9/29/02
to

ilias <at_...@pontos.net> writes:

> Fred Gilham wrote:
> >
> > There are a couple people whom I wish he could tolerate better
> > (because I enjoy hearing their input as well).
>
> hear, hear.
>
> > On the other hand,
> > there are a few people whose flame-job I think needs touching up[1]
> > that he has chosen to avoid addressing. :-)
>
> cannot decipher this. [1]
>
> >
> > I ran across a quotation that I don't have the attribution for but I
> > really like:
> >
> > Perhaps the greatest damage the American system of education has
> > done to its children is to teach them that their opinions are
> > relevant simply because they are their opinions.
> >
> > I've come to think this is not just the American system of education.
>
> let me guess: Norwegian, too.
>
> > It seems to be a global problem. I think people can say what they
> > want, that's their right. But there is no `right to be heard'. Being
> > heard must be earned. Many people don't realize that there's a
> > difference.
>
> i'll answer you with the words of the "immune high-intelligent bitter
> irrational egoistic disrespectful babbling puppeteer", which you may
> understand better:
>
> bullshit!
>
> >
> > [1] Cf. "Deal of the Century" w/Chevy Chase, Sigourney Weaver
>


ilias, did you think I meant you?

Wrong. (Hmn, I seem to be saying that too much, and it lacks a
certain politeness. How about "Senator, that happens not to be the
case." [1])

Of course your words are worthy of being heard. After all, it's ilias
that is speaking (or rather, writing).

Your problem is your choice of topic. Proper choice of topic is very
important.

AND to urge another Argument of a parallel Nature. If
Christianity were once abolished, how could the Free Thinkers,
the Strong Reasoners, and the Men of profound Learning, be able
to find another Subject so calculated in all Points whereon to
display their Abilities. What wonderful Productions of Wit
should we be deprived of, from those whose Genius by continual
Practice hath been wholly turn'd upon Railery and Invectives
against Religion, and would therefore never be able to shine or
distinguish themselves upon any other Subject. We are daily
complaining of the great decline of Wit among us, and would we
take away the greatest, perhaps the only Topick we have left?
Who would ever have suspected Asgil for a Wit, or Toland for a
Philosopher, if the inexhaustible Stock of Christianity had not
been at hand to provide them with Materials. What other Subject
through all Art or Nature could have produced Tindall for a
profound Author, or furnished him with Readers. It is the wise
Choice of the Subject that alone adorns and distinguishes the
Writer. For, had a Hundred such Pens as these been employed on
the side of Religion, they would have immediately sunk into
Silence and Oblivion. [2]


ilias, the above quotation is not meant for you to understand. I know
you are not concerned with getting something out of reading old, musty
books. I quoted it so that other readers could be made aware why your
intellect, obviously of such originality as to show no influence of
tutoring from any source, is having trouble displaying its true
magnitude in comp.lang.lisp.

I think you should choose some other topic than Lisp. It doesn't
really allow you to display your true intellectual power. Lisp users
depend far too much on their knowledge. They expect to be able to
read books and learn something from them. Worse, they are so
intolerant as to expect this from others as well. They constantly
refer questioners to books, papers, specifications and other worthless
material. They expect those with whom they interact to be capable of
understanding reasoned explanations as well as ideas of some
complexity.

Above all, they believe that a certain humility is necessary with
regard to learning. They believe that if you want to learn something,
you might have to stretch yourself and assume that someone else has
something to teach you. They believe that learners must sometimes
accommodate their thinking to that of their teachers. They believe
that knowledge is a progression, that things you learn later are built
on things you learn now or have learned in the past, and that you may
have to change yourself, bring yourself to a new level, in order to
understand something new. But your intellect is like the spheres of
the heavens, beyond change. It requires nothing but its own faculties
to instantly comprehend anything worth comprehending.

Clearly the Spirit of Lisp is foreign to someone like you, someone who
ignores reason in favor of a powerful, inexplicable intuition, who
uses every part of himself for thinking, even those parts usually
reserved for other functions such as sitting or reproduction. (What
inefficiency! How often does one reproduce? How much mass is
required for the simple act of sitting? Could not these parts play
another, more exalted role? --- In ilias they do.)

I therefore urge, even beg, you to find some topic more worthy of your
attention.

[1] From one of Tom Clancy's books.
[2] Jonathan Swift, "Against Abolishing Christianity"
--
Fred Gilham gil...@csl.sri.com
I think it's pretty obvious that the worship of that false idol known
as the State has, in the 20th Century, had some very bad effects. The
historians I'm familiar with have settled on the number of dead as 177
million, although I've seen estimates of up to 200 million.
-Bob Wallace

Jacek Podkanski

unread,
Sep 29, 2002, 1:59:00 PM9/29/02
to
Erik Naggum wrote:

> * Jacek Podkanski
> | Perhaps you are an expert with years of experience, but I am not. I
> | realise I ask daft questions and this one probably isn't last. You might
> | feel upset that someone asked such obvious question.
>
> It is not your "daft" questions that bother me, it is that you put
> people who
> answer you in an impossible situation. You ask people to confirm that
> you
> are right or correct you if you are wrong. This is actually unworkable.
> It may work for trivial questions of fact, but philosophical-like
> questions
> cannot be dealt with that way. And programming languages carry
> philosophies that you need to grasp before you grasp the programming
> language.

I admit I know little about Lisp philosophy. I didn't know if the question
was trivial or not. Confirming if I'm right or wrong reminds me of common
way of marking students work at school. Perhaps it is too shallow for Lisp,
but I didn't realise that philosophy could be so important to a programming
language.

>
> | Tell me haw many years ago last time you asked a question which could be
> | daft to an expert. Even if it was ages ago you had to start somewhere.
>
> Here you assume that everybody else is just like you. This is just not
> the

Ooooops.

> case. Until you realize that you have a counter-producitve approch to
> the whole knowledge-acquisition process, you will not really figure
> anything out,

I don't think my approach is counter-productive, it's just different. In a
long term I think it can be as good as yours.

> but you will /think/ you do. The desire you exhibit to be /correct/ is
> the
> only thing that is really "daft" here. Things are not "correct". When
> you are in the learning phase, things have a different meaning than when
> you are
> more experienced. Concepts are usually disconnected when you new to a
> field and sentences change meaning as you connect the underlying
> concepts.
>
> I have always been humble towards knowledge I do not have, of systems I
> do
> not know, of philosophies that I do not know. What makes it able to
> learn very quickly is that I listen to what experienced people say and
> ask them the
> questions that will help me connect things. My goal is understand as

I hoped that asking the question I would be able to connect things.

> deeply
> as possible what is going on around me. I have no use for sentences
> whose
> meaning I do not know, but which other people say is "correct". If I

This approach has helped me to learn english language.

I'd think that I belong to the second "/become/ correct" group.


>
> Just because you are a novice does not mean that you ask "daft"
> questions. You do not have to be an expert to realize that "correct me
> if I'm wrong" is a recipe for grave mistakes and serious confusion down
> the line.

If answer is very simple it doesn't have to be so. I thought that answer to
my question would be quite simple.


>
> Just over three weeks ago, I wrote a scathing review of a manuscript on
> the Semantic Web, after having spent another three weeks with that
> manuscript. Then I visited my local library and talked with their staff
> and learned that the 5th edition of the Norwegian adaption of the Dewey
> Decimal Classification
> was just around the corner. I acquired the books and got all excited
> about the ability to use this enormous and ongoing work for managing the
> "ontology"
> of the Semantic Web. I have since then been communicating with almost
> 50 people in national libraries in Norway, England, Germany, and the
> U.S., and
> several large public libraries in Norway. According to some, I have
> come up to speed in two weeks compared with the two years fresh college
> students in
> information and library science require to understand the same isuses.
> This is not because I am old and very experienced and have always
> learned quickly, but because I /listen/ to people who more than I do and
> because I am willing to put in 16 hours a day to learn something from
> the best available sources. Keep learning new things by spending two

My problem was a quality of source that caused some confusion, I think.

> hours studying something you have no immediate use for as a daily
> routine for three decades, and you just know a lot and can connect a lot
> more dots than if you only learn while "forced" to
> by teachers and exams and the like. Add good methodology and things
> come
> real easy after a while. With no "daft" questions in sight. Avoiding
> stupid questions is /not/ intractable, just ask intelligent questions,
> meaning those whose answers actually mean something to you personally
> and actually help you understand something at your current level of
> expertise.

Actually the question has meant something to me. I was wondering if I could
implement sort of Lisp macros in a scripting language I use. Making in the
process connections with things I know, or even learning from my mistakes
if I fail.

> Some say there are no stupid questions, but this is a lie. A stupid
> question is a question to which the answer would not benefit the
> questioner.
>
> | It's just easier sometimes to get an answer from a human than looking
> | for it through the books.
>
> Books give you the clear advantage that you learn at your own pace. The
> books were written by people who were trained in presenting the material
> in a pedagogical manner, their manuscripts went through several drafts,
> and the people who reviewed it have slaughtered parts of it and
> encouraged other
> parts. A book is an immense cooperative project. Any given individual
> you ask will require a personal rapport with your prior understanding
> before he can provide you with useful and contextually relevant and
> correct answers. You need to be aware of this process when you ask
> questions and receive answers to them.

If I don't get megabytes of an answer, I am sure I can do it at my own pace.

I think a book has less chance to guess how much I know than a human can do.

There's one problem, most Lisp documentation I downloaded now is in
PostScript or PDF, and viewer I use doesn't have word search capability.

Conclusion:
Because I am new to this group I decided to spend time discussing things
with you because I will make possible to know each other a bit better. I
hope it will help a bit to get rid of some kind of communication problem
you and me have.

--
Jacek Podkanski

ilias

unread,
Sep 29, 2002, 2:25:56 PM9/29/02
to
Fred Gilham wrote:
[...]

many many things bounded to knowledge, which i'm not able to decipher.

cause i'm undereducated.

> I therefore urge, even beg, you to find some topic more worthy of your
> attention.

rejected.

Fred Gilham

unread,
Sep 29, 2002, 2:58:16 PM9/29/02
to

Ilias wrote:
> many many things bounded to knowledge, which i'm not able to
> decipher.
>
> cause i'm undereducated.
>
> > I therefore urge, even beg, you to find some topic more worthy of
> > your attention.
>
> rejected.

How foolish of me. Clearly I should have known better --- I had
already stated that ilias was beyond change:

"But your intellect is like the spheres of the heavens, beyond change."

Hmn, there really are other things I could be doing....

--
Fred Gilham gil...@csl.sri.com

Is, then, the loving cup so often filled
that we may toss a draught aside?....
-Jeff Iverson

ilias

unread,
Sep 29, 2002, 3:14:16 PM9/29/02
to
Fred Gilham wrote:
> Ilias wrote:
>
>>many many things bounded to knowledge, which i'm not able to
>>decipher.
>>
>>cause i'm undereducated.
>>
>>
>>>I therefore urge, even beg, you to find some topic more worthy of
>>>your attention.
>>
>>rejected.
>
>
> How foolish of me. Clearly I should have known better --- I had
> already stated that ilias was beyond change:
>
> "But your intellect is like the spheres of the heavens, beyond change."
>
> Hmn, there really are other things I could be doing....
>

amen

Kaz Kylheku

unread,
Sep 29, 2002, 3:42:30 PM9/29/02
to
Barry Margolin <bar...@genuity.net> wrote in message news:<xa3l9.36$AO3....@paloalto-snr1.gtei.net>...

> (defstruct foo a b c)
>
> becomes
>
> (create-structure 'foo 'a 'b 'c)

Why not take this to its ultimate conclusion:

(interpreter-function-for-language-with-macros '(defstruct foo a b
c))

Now the real trick is to get the interpreted code to interoperate
nicely with the surrounding lexical environment. Defstruct operates on
global associations, so it is easy. The slot names a, b and c have no
relationship to any surrounding material.

This is what you can't do with Lisp functions: pass down the calling
lexical environment. You can pass down closures over that environment,
but it's encapsulated.

Given a language in which you can express something like:

(defun my-interpreter (&env calling-environment &rest forms)
... transform and interpret forms in calling environment
)

functions could implement a more reasonable approximation of macros.

Vassil Nikolov

unread,
Sep 29, 2002, 5:26:15 PM9/29/02
to
Jacek Podkanski <jacekpo...@supanet.com> writes:

[...]


> It's just easier sometimes to get an answer from a human than
> looking for it through the books.

By the way, what is often easy is _asking_ a human, or a group of
humans, for an answer. However, _giving_ a good answer may not be
easy for those that can give one, so a possible outcome is no answer
or a bad answer. Thus reading a good book may be more productive
since that good answer would already be there.

Besides, for some answers one just has to read the book through, so
a word search capability is not really necessary.

The intersection of the easy ways and the ways that lead to good
results is not large (if at all non-empty). But I have repeated,
in too many words, that famouse phrase about the royal road to
learning...

---Vassil.

Will Deakin

unread,
Sep 29, 2002, 6:36:07 PM9/29/02
to
Vassil Nikolov wrote:
> ...But I have repeated, in too many words, that famouse

> phrase about the royal road to learning...
Is this like the famous Laurel and Hardy saying `You can lead a horse
to water but a pencil must be lead'...

;)w

Erik Naggum

unread,
Sep 29, 2002, 8:27:59 PM9/29/02
to
* Jacek Podkanski

| I admit I know little about Lisp philosophy.

It is also hard to explain to someone who does not know the language, and
since those who do, tend to agree on it, it is not often verbalized. The
great thing about philosophers is that the are able to zoom out and look at
that which other people take for granted and explain it in intelligent ways.
I have search for and read a number of articles and books that have at least
had pretentions of explaining the philosophy of programming, but I have not
found any. Still, some books that I have found useful:

DDC 005.1019, ISBN 0-932633-42-0, LCCN 98038794, 1998
Gerald M. Weinberg
The Psychology of Computer Programming

DDC 005.1, ISBN 0-201--61586-X, LCCN 9910131, 1999
Brian W. Kernighan, Rob Pike
The Practice of Programming

DDC 005.133, ISBN 0-201-54330-3, LCCN 93050758, 1994
Bjarne Stroustrup
The Design and Evolution of C++

DDC 005.1, ISBN 0-262-14053-5, LCCN 93009124, 1993
Bonnie A. Nardi
A Small Matter of Programming: Perspective on End User Comuting

DDC 005.1, ISBN 0-201-61622-X, LCCN 99043581, 2000
Andrew Hunt, David Thomas
The Pragmatic Programmer: from Journeyman to Master

These exemplify approaches to programming that are philosophical in nature,
although the philosophy itself is just below the surface, not explicit. Where
mathematics has Keith Devlin or John Allan Paulos, there is no equivalent for
computing.

| Confirming if I'm right or wrong reminds me of common way of marking students
| work at school.

This happens precisely in the intimate relationship between questioner
(student) and answerer (teacher/nestor) that I tried to explain that does not
exist until you have made yourself more known to those who could answer you.
A teacher who asks a question knows precisely what the answer is expected to
mean. In fact, one of the reasons that those who learn well on their own and
go off to devour the entire library have a hard time dealing with grading
from their teachers is that they lose track of their teachers' expectations
and the context in which both questions and answers are normally given.

| Perhaps it is too shallow for Lisp, but I didn't realise that philosophy
| could be so important to a programming language.

This means that you have only accepted one philosophy and are probably
completely unaware of it. When you find a different programming language,
such as Common Lisp is (and Haskell and Prolog and Forth), your problems are
first and foremost philosophical when you try to understand what they are all
about, and those who have no philosophical bent learn only one paradigm.

| I don't think my approach is counter-productive, it's just different. In a
| long term I think it can be as good as yours.

Of course you do. This is part of the problem.

| I hoped that asking the question I would be able to connect things.

That may well be, but you did not give your potential answerers any clue as
to what you would connect as the result of the answer. Therefore, a correct
answer could have deleterious consequences.

| This approach has helped me to learn english language.

Oh, you are not a native speaker. Not that I noticed, but this could explain
why you (appear to) think statements have only one meaning. English is
delightfully able to capture a whole slew of nuances with a single sentence
and has a highly poetic nature with a rich flow of imagery and connotations
under the surface denotations. Several other European languages are much
more sterile and have significant differences between their poetic form and
their straightforward day-to-day form.

| If answer is very simple it doesn't have to be so. I thought that answer to
| my question would be quite simple.

Precisely. This misguided idea is what I really wanted to correct.

| Actually the question has meant something to me. I was wondering if I could
| implement sort of Lisp macros in a scripting language I use. Making in the
| process connections with things I know, or even learning from my mistakes if
| I fail.

Well, to understand macros, you need to understand the different evaluation
times of Common Lisp, which differ dramatically from other languages. E.g.,
when an expression is interpreted, a macro form is expanded and then
interpreted in order, before the next form, but when compilng, the macro form
is expanded at compile-time, and the compiler emits instructions to the
target execution environment to produce the same results as if it were
interpreted. This both affects and is affected by the amount and kind of
information available at each evaluation time in subtle ways. Macros may
cuase information to be available to other macros, but not in the run-time
environment. These differences are quite hard to explain, but as I hope you
will see, they make for profound differences between macros and lambdas.

| I think a book has less chance to guess how much I know than a human can do.

The key was really to make you aware of the guesswork involved and then to
minimize it. Books are good /because/ they force you to understand and
accept the context of another person. Requiring others to guess your context
is not very polite in addition to being massively error-prone. I liked Rob
Warnick's response to my note as it highlights the kind of interactions that
most people do not reflect on.

| There's one problem, most Lisp documentation I downloaded now is in
| PostScript or PDF, and viewer I use doesn't have word search capability.

Then read them from start to end.

| Because I am new to this group I decided to spend time discussing things with
| you because I will make possible to know each other a bit better. I hope it
| will help a bit to get rid of some kind of communication problem you and me
| have.

Not a bad strategy. I hope this helps.

Jacek Podkanski

unread,
Sep 30, 2002, 7:40:16 AM9/30/02
to
Erik Naggum wrote:

Don't know if I will ever have chance to read all the books you mention,
but my favourite authors are Andrew Hunt and David Thomas. Reading their
documentation of Ruby language I stumbled across suggestion to learn other
programming languages to expand ones horizons. This is one of reasons I
started learning Lisp.


>
> These exemplify approaches to programming that are philosophical in
> nature, although the philosophy itself is just below the surface, not
> explicit. Where mathematics has Keith Devlin or John Allan Paulos, there
> is no equivalent for computing.
>
> | Confirming if I'm right or wrong reminds me of common way of marking
> | students work at school.
>
> This happens precisely in the intimate relationship between questioner
> (student) and answerer (teacher/nestor) that I tried to explain that
> does not exist until you have made yourself more known to those who
> could answer you. A teacher who asks a question knows precisely what the
> answer is expected to
> mean. In fact, one of the reasons that those who learn well on their
> own and go off to devour the entire library have a hard time dealing
> with grading from their teachers is that they lose track of their
> teachers' expectations and the context in which both questions and
> answers are normally given.
>
> | Perhaps it is too shallow for Lisp, but I didn't realise that philosophy
> | could be so important to a programming language.
>
> This means that you have only accepted one philosophy and are probably
> completely unaware of it. When you find a different programming

I hoped that I stopped thinking in Basic ages ago, but maybe I'm wrong.

I'd rather use expression way of thinking, than philosophy. I'd rather
acquire new ideas to help me adapt way of thinking that will help me better
to solve problems without love of the way of thinking as it is with
philosophy

> language, such as Common Lisp is (and Haskell and Prolog and Forth),
> your problems are first and foremost philosophical when you try to
> understand what they are all about, and those who have no philosophical
> bent learn only one paradigm.

You don't need philosophy to learn different paradigm. Learning foreign
language will do.


>
> | I don't think my approach is counter-productive, it's just different.
> | In a long term I think it can be as good as yours.
>
> Of course you do. This is part of the problem.
>
> | I hoped that asking the question I would be able to connect things.
>
> That may well be, but you did not give your potential answerers any clue
> as
> to what you would connect as the result of the answer. Therefore, a
> correct answer could have deleterious consequences.

I didn't expect it would be such problem. I'll think about my question
before I post it next time.


>
> | This approach has helped me to learn english language.
>
> Oh, you are not a native speaker. Not that I noticed, but this could
> explain
> why you (appear to) think statements have only one meaning. English is

I think this is essence of our misunderstanding. Looks like that you try to
think about all possible meanings, while I filter out all except few
obvious ones. Thats why I didn't expect too much problems when I initially
asked my question, while you found it hard to give useful answer. I do
realise that sometimes it is better if I use your strategy, but on many
occasions my will do.

> delightfully able to capture a whole slew of nuances with a single
> sentence and has a highly poetic nature with a rich flow of imagery and
> connotations
> under the surface denotations. Several other European languages are
> much more sterile and have significant differences between their poetic
> form and their straightforward day-to-day form.

When discussing computer related subjects I didn't expect that poetry and
and multiple meanings should be taken into consideration. And my mother
tongue is "more sterile". Maybe this added to my problem.


>
> | If answer is very simple it doesn't have to be so. I thought that
> | answer to my question would be quite simple.
>
> Precisely. This misguided idea is what I really wanted to correct.

It's my approach, sometimes initially I'm not bothered to be totally
correct, but rather have some general overview of the subject, and then I
try to understand things better, connect the facts and start filling the
gaps in my knowledge.

>
> | Actually the question has meant something to me. I was wondering if I
> | could
> | implement sort of Lisp macros in a scripting language I use. Making in
> | the process connections with things I know, or even learning from my
> | mistakes if I fail.
>
> Well, to understand macros, you need to understand the different
> evaluation
> times of Common Lisp, which differ dramatically from other languages.
> E.g., when an expression is interpreted, a macro form is expanded and
> then interpreted in order, before the next form, but when compilng, the
> macro form is expanded at compile-time, and the compiler emits
> instructions to the target execution environment to produce the same
> results as if it were
> interpreted. This both affects and is affected by the amount and kind
> of
> information available at each evaluation time in subtle ways. Macros
> may cuase information to be available to other macros, but not in the
> run-time
> environment. These differences are quite hard to explain, but as I hope
> you will see, they make for profound differences between macros and
> lambdas.

I think that if you initially answered that way I would be satisfied with
it. But then we wouldn't have that correspondence about lots of other
interesting things.

> | I think a book has less chance to guess how much I know than a human can
> | do.
>
> The key was really to make you aware of the guesswork involved and then
> to
> minimize it. Books are good /because/ they force you to understand and
> accept the context of another person. Requiring others to guess your
> context
> is not very polite in addition to being massively error-prone. I liked
> Rob Warnick's response to my note as it highlights the kind of
> interactions that most people do not reflect on.

Sorry about that. Next time I will try to provide more context.

>
> | There's one problem, most Lisp documentation I downloaded now is in
> | PostScript or PDF, and viewer I use doesn't have word search capability.
>
> Then read them from start to end.

It takes some time to read more than hundred pages and then remembering
where required information is.


>
> | Because I am new to this group I decided to spend time discussing things
> | with
> | you because I will make possible to know each other a bit better. I
> | hope it will help a bit to get rid of some kind of communication problem
> | you and me have.
>
> Not a bad strategy. I hope this helps.

So do I.

--
Jacek Podkanski

Thien-Thi Nguyen

unread,
Sep 30, 2002, 11:41:02 AM9/30/02
to
Jacek Podkanski <jacekpo...@supanet.com> writes:

> I'd rather use expression way of thinking, than philosophy. I'd rather
> acquire new ideas to help me adapt way of thinking that will help me
> better to solve problems without love of the way of thinking as it is
> with philosophy

almost. philosophy is the love (and subsequent study, characterization,
and postulation) of the way*s* of thinking (plural).

anyway, when you say "i'd rather ..." you are philosophizing to some
degree. people who program lisp a lot are urging you to expand your
philosophy, not replace it. in doing so, you expand your ability to
grok lisp and ultimately your facility and joy in the pratice of lisp
programming. this can be said of any language, so why not lisp?

thi

Thomas F. Burdick

unread,
Sep 30, 2002, 2:20:40 PM9/30/02
to
k...@ashi.footprints.net (Kaz Kylheku) writes:

> Barry Margolin <bar...@genuity.net> wrote in message news:<xa3l9.36$AO3....@paloalto-snr1.gtei.net>...
> > (defstruct foo a b c)
> >
> > becomes
> >
> > (create-structure 'foo 'a 'b 'c)
>
> Why not take this to its ultimate conclusion:
>
> (interpreter-function-for-language-with-macros '(defstruct foo a b
> c))

Unless there's a good reason to do otherwise, I really prefer deffoo
macros to expand into a call to an ensure-foo function. Much like
DEFCLASS => ENSURE-CLASS -- that way you can have the nice syntax when
you want it, but you can also programatically generate things when you
need to (without calling eval, or my-eval, or
my-eval-with-a-really-long-name or whatever :).

--
/|_ .-----------------------.
,' .\ / | No to Imperialist war |
,--' _,' | Wage class war! |
/ / `-----------------------'
( -. |
| ) |
(`-. '--.)
`. )----'

Jacek Podkanski

unread,
Sep 30, 2002, 2:32:09 PM9/30/02
to
Thien-Thi Nguyen wrote:

I just don't want to engage in never ending philosophical disputes and
speculations. Starting to learn Lisp I hoped to expand my ways of thinking
or expand my horizons, which is almost the same.
--
Jacek Podkanski

0 new messages