From: Mark Carter
Subject: Newbie macro puzzle
Date: 
Message-ID: <44c89dcc$0$15795$14726298@news.sunsite.dk>
I'm trying to define a new macro, llet*, so that instead of doing
(let* ((a b) (1 2))
       (print a)
      ...)

I can do

(llet* '(a b) '(1 2)
        (print a)
        ...)

There are 2 issues here:
1. is there already a Lisp function/macro that allows me to do such a thing?

2. how would I reproduce it? Here's what I've got so far:

(defun meshl (list1 list2)
   (mapcar #'list list1 list2))
(meshl '(a b) '(1 2)) => '((A 1) (B 2)) ;; this is what I expect

(defmacro llet* ( lval rval &body body )
     `(let* ,(meshl lval rval)
        ,@body))

So if I do
(llet*  '(a b) '(1 2)
        (print a))
I expect to print out the value 1. Except that it's not happening.
I tried
(macroexpand-1 '(llet*  '(a b) '(1 2)
        (print a)))
and I get
(LET* ('QUOTE ((A B) (1 2))) (PRINT A))
which is not what I was expecting at all. What should I be doing?

From: Pascal Costanza
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <4irnutF55b9mU1@individual.net>
Mark Carter wrote:
> 
> 
> I'm trying to define a new macro, llet*, so that instead of doing
> (let* ((a b) (1 2))
>       (print a)
>      ...)
> 
> I can do
> 
> (llet* '(a b) '(1 2)
>        (print a)
>        ...)
> 
> There are 2 issues here:
> 1. is there already a Lisp function/macro that allows me to do such a 
> thing?

You can approximate this with multiple-value-bind or destructuring-bind:

(multiple-value-bind
   (a b) (values 1 2)
   (print a))

(destructuring-bind
   (a b) (list 1 2)
   (print a))

Multiple-value-bind is more efficient because it doesn't need to create 
a list at runtime.

> 2. how would I reproduce it? 

Why do you have quotes in your llet* form? In other words, why do you 
want to say '(a b)?

Hint: Can you implement a simpler version of this? For example:

(bind (('a 1) ('b 2)) (print a))

which should do the equivalent of this:

(let ((a 1) (b 2)) (print a))

Question: What is the result of the following, and what should it expand 
into?

(defvar *var* 'a)

(bind ((*var* 1)) (print a))


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Mark Carter
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <44c8b136$0$15792$14726298@news.sunsite.dk>
Pascal Costanza wrote:

> Why do you have quotes in your llet* form? In other words, why do you 
> want to say '(a b)?

So far, I have

(defparameter *schema*
   '(
     (H2O-CONT 0 () (C0 C1 C2 C3 C4))
     (TESTFLOW 0 (WELL) (TESTGAS TESTOIL LIFTGAS))
     (TESTCOND 0 (WELL) (T_D101 TP T_D103))
     (GAS-RATE 1 (WELL) (GAS-RATE))
     ))

(defparameter *schema-meaning*
   '(group-name skip-cols dependencies input-names))

and I am trying to put together the function process-entries:

(defun process-entries (schema-entry input-entries)
   (llet* *schema-meaning* schema-entry
	... do stuff))

Here, input-entries are inputs from a data file relating to a particular 
entry in the schema (e.g. (H2O-CONT 0 () (C0 C1 C2 C3 C4))). 
process-entries "does something" to the inputs (more specifically, it 
builds up a lookup table of values for the input-names).

I want to know what's in the schema line that I'm looking at, so setting 
group-name to 'H2O-CONT, and skip-cols to 0, etc. seems like a good idea 
... which explains why I want to use '(a b) instead of (a b).
From: Pascal Bourguignon
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <87bqrbj68i.fsf@thalassa.informatimago.com>
Mark Carter <··@prviacy.net> writes:

> Pascal Costanza wrote:
>
>> Why do you have quotes in your llet* form? In other words, why do
>> you want to say '(a b)?
>
> So far, I have
>
> (defparameter *schema*
>   '(
>     (H2O-CONT 0 () (C0 C1 C2 C3 C4))
>     (TESTFLOW 0 (WELL) (TESTGAS TESTOIL LIFTGAS))
>     (TESTCOND 0 (WELL) (T_D101 TP T_D103))
>     (GAS-RATE 1 (WELL) (GAS-RATE))
>     ))
>
> (defparameter *schema-meaning*
>   '(group-name skip-cols dependencies input-names))
>
> and I am trying to put together the function process-entries:
>
> (defun process-entries (schema-entry input-entries)
>   (llet* *schema-meaning* schema-entry
> 	... do stuff))
>
> Here, input-entries are inputs from a data file relating to a
> particular entry in the schema (e.g. (H2O-CONT 0 () (C0 C1 C2 C3
> C4))). process-entries "does something" to the inputs (more
> specifically, it builds up a lookup table of values for the
> input-names).
>
> I want to know what's in the schema line that I'm looking at, so
> setting group-name to 'H2O-CONT, and skip-cols to 0, etc. seems like a
> good idea ... which explains why I want to use '(a b) instead of (a
> b).

What you're explaining is that you have some data at run-time and that
you want to build a program from it, at run-time.  You don't need a
macro to do that.


[7]> (with-input-from-string 
    (in "(a b c) 
         ((+ 1 2) (* 3 4) (/ 5 6))
         ((print a) (print b) (print c) nil)")
  (let ((vars (read in))
        (vals (read in))
        (body (read in)))
    `(lambda () (let ,(mapcar (lambda (var val) `(,var ,val)) vars vals) ,@body))))

(LAMBDA NIL
 (LET ((A (+ 1 2)) (B (* 3 4)) (C (/ 5 6))) (PRINT A) (PRINT B) (PRINT C) NIL))
[8]> (compile nil *)
#<COMPILED-FUNCTION NIL> ;
NIL ;
NIL
[9]> (funcall *)

3 
12 
5/6 
NIL
[10]> 

However, if you want to allow free variables in the body, the you'll
have to collect them, and pass them as parameter to the lambda
function you're building.  But you still don't need a macro to do that.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
You never feed me.
Perhaps I'll sleep on your face.
That will sure show you.
From: Pascal Costanza
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <4isf2qF58edqU1@individual.net>
Mark Carter wrote:
> Pascal Costanza wrote:
> 
>> Why do you have quotes in your llet* form? In other words, why do you 
>> want to say '(a b)?
> 
> So far, I have
> 
> (defparameter *schema*
>   '(
>     (H2O-CONT 0 () (C0 C1 C2 C3 C4))
>     (TESTFLOW 0 (WELL) (TESTGAS TESTOIL LIFTGAS))
>     (TESTCOND 0 (WELL) (T_D101 TP T_D103))
>     (GAS-RATE 1 (WELL) (GAS-RATE))
>     ))
> 
> (defparameter *schema-meaning*
>   '(group-name skip-cols dependencies input-names))
> 
> and I am trying to put together the function process-entries:
> 
> (defun process-entries (schema-entry input-entries)
>   (llet* *schema-meaning* schema-entry
>     ... do stuff))

If you really want to make this work, what you could do is to compute 
the code at read time:

(eval-when (:compile-toplevel :load-toplevel :execute)
   (defparameter *schema-meaning*
     '(group-naming skip-cols dependencies input-names)))

(defun process-entries (schema-entry input-entries)
   (multiple-value-bind
     #.*schema-meaning* schema-entry
     ...))

You would lose the ability to change *schema-meaning at runtime, but I 
find it hard to imagine what this could buy you without changing the 
definition of process-entries at the same time.

Apart from that, it seems to me that an object-oriented style could help 
you to simplify the code:

(defclass schema ()
   ((group-name :initarg :group-name)
    ...))

(defun process-entries (schema-entry input-entries)
   (with-slots (group-name ...) schema-entry
     ...))

However, you would still have to know statically what slots you have.


Why do you want the *schema-meaning* to change at runtime, and how 
should this affect process-entries?


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Mark Carter
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <44c91d00$0$15788$14726298@news.sunsite.dk>
Pascal Costanza wrote:

> Why do you want the *schema-meaning* to change at runtime, and how 
> should this affect process-entries?

You're right enough, the schema wont change at runtime. Perhaps 
exploring classes is a good idea (although the last time I tried using 
classes in Lisp, it gave me no end of problems).
From: Lars Brinkhoff
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <85k65zqaho.fsf@junk.nocrew.org>
Pascal Costanza <··@p-cos.net> writes:
> Mark Carter wrote:
>> I'm trying to define a new macro, llet*, so that instead of doing
>> (let* ((a b) (1 2))
>>       (print a)
>>      ...)
>> I can do
>> (llet* '(a b) '(1 2)
>>        (print a)
>>        ...)

That looks like PROGV, but keep in mind it does special bindings.

> (multiple-value-bind
>    (a b) (values 1 2)
>    (print a))
>
> (destructuring-bind
>    (a b) (list 1 2)
>    (print a))
>
> Multiple-value-bind is more efficient because it doesn't need to
> create a list at runtime.

(with-nit-picking
  Not necessarily.  I'd rather say that destructuring-bind is more
  likely to be less efficient, because compilers may not optimize away
  the run-time list creation.)
From: Barry Margolin
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <barmar-BCB631.18200627072006@comcast.dca.giganews.com>
In article <··············@junk.nocrew.org>,
 Lars Brinkhoff <·········@nocrew.org> wrote:

> Pascal Costanza <··@p-cos.net> writes:
> > Mark Carter wrote:
> >> I'm trying to define a new macro, llet*, so that instead of doing
> >> (let* ((a b) (1 2))
> >>       (print a)
> >>      ...)
> >> I can do
> >> (llet* '(a b) '(1 2)
> >>        (print a)
> >>        ...)
> 
> That looks like PROGV, but keep in mind it does special bindings.

If the variables to be bound won't be known until runtime, special 
binding is all that's feasible.  Lexical binding, by its very nature, 
requires the variables to be known at compile time.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
*** PLEASE don't copy me on replies, I'll read them in the group ***
From: Kent M Pitman
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <uslkmz8m3.fsf@nhplace.com>
Barry Margolin <······@alum.mit.edu> writes:

> In article <··············@junk.nocrew.org>,
>  Lars Brinkhoff <·········@nocrew.org> wrote:
> 
> > Pascal Costanza <··@p-cos.net> writes:
> > > Mark Carter wrote:
> > >> I'm trying to define a new macro, llet*, so that instead of doing
> > >> (let* ((a b) (1 2))
> > >>       (print a)
> > >>      ...)
> > >> I can do
> > >> (llet* '(a b) '(1 2)
> > >>        (print a)
> > >>        ...)
> > 
> > That looks like PROGV, but keep in mind it does special bindings.
> 
> If the variables to be bound won't be known until runtime, special 
> binding is all that's feasible.  Lexical binding, by its very nature, 
> requires the variables to be known at compile time.

Well, mostly.  There is the special case of LET-IF where you can
finitely enumerate the cases and theoretically implement this using
lexicality (although I think the LispM implementation preferred to
dynamically bind anyway).

Also, whether that qualifies as "knowing the variables to be bound" or
not is a subjective assessment--you know the names of all the sets of
variables.  e.g., you might have a construct like

 (defmacro my-let-if (condition bindings &body forms)
   `(if ,condition
        (let ,bindings ,@forms)
        (progn ,@forms)))

even though it's hard to imagine actually using it. It would require
you to do something like:

 (let ((x 'default-value-of-x))
   (my-let-if *use-better-x* ((x *better-x*))
     (list 'answer-is x)))

But yes, usually the more rational interface is:

 (defmacro my-progw (bindings-evaluated &body forms) 
   ;; The LispM had a version of PROGV that I liked better. It was
   ;; called PROGW and it took something more like a binding list
   ;; rather than a list of vars and another list of values.
   ;; I don't have a LispM manual handy, so maybe someone who does can
   ;; correct me if I've got the semantics wrong.
   (let ((bindings-var (gensym "BINDINGS")))
     `(let ((,bindings-var ,bindings-evaluated))
        (progv (mapcar #'(lambda (x) (if (atom x) x   (car x)))
                       ,bindings-var)
               ;; Some might prefer (eval (cadr x)) here, but I figure
               ;; that bindings-evaluated already had a chance at eval,
               ;; so no extra eval is needed around (cadr x).
               (mapcar #'(lambda (x) (if (atom x) nil (cadr x)))
                       ,bindings-var)
          ,@forms))))

  (defvar *use-better-x* t)
  (defvar *some-x* 'default-value-of-x)
  (defvar *better-x* 'another-value-of-x)

  (my-progw (if *use-better-x* `((*some-x* ,*better-x*)) '())
    (list 'answer-is *some-x*))

... or some such.  (After all that discussion of free-software,
my mind is glazed and I'm not bothering to start a Lisp and test
that what I wrote above works.  It's late and I'm sleepy, so
caveat emptor.)
From: Lars Brinkhoff
Subject: Handling declarations
Date: 
Message-ID: <85ac6uqm1q.fsf_-_@junk.nocrew.org>
Kent M Pitman <······@nhplace.com> writes:
> you might have a construct like
>
>  (defmacro my-let-if (condition bindings &body forms)
>    `(if ,condition
>         (let ,bindings ,@forms)
          (locally ,@forms)))           ;slight alteration

How do experienced Lispers write macros such as this to handle
declarations in the body?  I.e. if FORMS has any declarations for
variables in BINDINGS, you would like to include those in the body of
LET, but not in LOCALLY.

(Please disregard any problems with using lexical bindings in this
particular example.)
From: Rob Warnock
Subject: Re: Handling declarations
Date: 
Message-ID: <-YydnRuCt84ETVTZnZ2dnUVZ_radnZ2d@speakeasy.net>
Lars Brinkhoff  <·········@nocrew.org> wrote:
+---------------
| Kent M Pitman <······@nhplace.com> writes:
| > you might have a construct like
| >
| >  (defmacro my-let-if (condition bindings &body forms)
| >    `(if ,condition
| >         (let ,bindings ,@forms)
|           (locally ,@forms)))           ;slight alteration
| 
| How do experienced Lispers write macros such as this to handle
| declarations in the body?  I.e. if FORMS has any declarations for
| variables in BINDINGS, you would like to include those in the body of
| LET, but not in LOCALLY.
+---------------

I don't know the portable way, if any, but CMUCL provides an
extension to macro LAMBDA lists which helps with this, the
&PARSE-BODY (&optional body decls doc-strings) keyword, which
could be used to do what you want [I think]:

  (defmacro my-let-if (condition bindings &body (forms decls))
    (multiple-value-bind (binding-decls other-decls)
	(split-decls bindings decls)
      `(if ,condition
	 (let ,bindings ,@binding-decls ,@other-decls ,@forms)
	 (locally ,@other-decls ,@forms))))

where SPLIT-DECLS is left as an exercise for the reader.  ;-}  ;-}

By the way, here's how CMUCL uses &PARSE-BODY to define DEFUN itself:

  (defmacro defun (&whole source name lambda-list &parse-body (body decls doc))
    (multiple-value-bind (valid block-name)
	(valid-function-name-p name)
      (declare (ignore valid))
      (let ((def `(lambda ,lambda-list
		    ,@decls
		    (block ,block-name ,@body))))
	`(c::%defun ',name #',def ,doc ',source))))

The DECLS are separated out so that they can be placed in front of
the BLOCK which wraps BODY (and names it so RETURN-FROM will work).


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Lars Brinkhoff
Subject: Re: Handling declarations
Date: 
Message-ID: <85odvaowaa.fsf@junk.nocrew.org>
····@rpw3.org (Rob Warnock) writes:
> Lars Brinkhoff  <·········@nocrew.org> wrote:
> > Kent M Pitman <······@nhplace.com> writes:
> > > you might have a construct like
> > >  (defmacro my-let-if (condition bindings &body forms)
> > >    `(if ,condition
> > >         (let ,bindings ,@forms)
> >           (locally ,@forms)))           ;slight alteration
> > How do experienced Lispers write macros such as this to handle
> > declarations in the body?  I.e. if FORMS has any declarations for
> > variables in BINDINGS, you would like to include those in the body of
> > LET, but not in LOCALLY.
> 
> CMUCL provides an extension to macro LAMBDA lists which helps with
> this, the &PARSE-BODY (&optional body decls doc-strings) keyword

Yes, that's a part of the solution.  In my toolbox I have a PARSE-BODY
function which separates a body into those three parts (or two, for
the cases where there is no doc string).  So far, so good, so portable.

However...

>   (defmacro my-let-if (condition bindings &body (forms decls))
>     (multiple-value-bind (binding-decls other-decls)
> 	(split-decls bindings decls)
>       `(if ,condition
> 	 (let ,bindings ,@binding-decls ,@other-decls ,@forms)
> 	 (locally ,@other-decls ,@forms))))
>
> where SPLIT-DECLS is left as an exercise for the reader.  ;-}  ;-}

...it was really this SPLIT-DECLS I was hoping to read more about.
Though actually, I think getting all declarations relating to some
specific variable (or list of variables) might be more useful.

This issue seems to come up occasionally in user-level macro writing,
so I'd be surprised if there was no solution.  Of course, it's hard to
handle implementation-specific and user-defined declarations.
From: Rob Warnock
Subject: Re: Handling declarations
Date: 
Message-ID: <RvadndDqxdJ4UFfZnZ2dnUVZ_u-dnZ2d@speakeasy.net>
Lars Brinkhoff  <·········@nocrew.org> wrote:
+---------------
| ····@rpw3.org (Rob Warnock) writes:
| > (defmacro my-let-if (condition bindings &body (forms decls))
| >   (multiple-value-bind (binding-decls other-decls)
| >       (split-decls bindings decls)
| >     `(if ,condition
| >        (let ,bindings ,@binding-decls ,@other-decls ,@forms)
| >        (locally ,@other-decls ,@forms))))
| >
| > where SPLIT-DECLS is left as an exercise for the reader.  ;-}  ;-}
| 
| ...it was really this SPLIT-DECLS I was hoping to read more about.
+---------------

Well, it seemed sort of obvious, but I was in a rush [and don't
need it myself], so I waved the "exercise for the reader" magic wand.  ;-}
Basically, I supposed that SPLIT-DECLS would trundle down the list
of DECLS looking for any that applied to (MAPCAR #'CAR BINDINGS),
and separate those out. There's a bit of scut work to do there,
making sure you handle all the variations of declaration syntax,
but my gut feel is that it's maybe 0.5-1.0 pages of code.

+---------------
| Though actually, I think getting all declarations relating to some
| specific variable (or list of variables) might be more useful.
+---------------

If you do that sort of thing often, then this is certainly
the sort of routine you would want to have around.  ;-}

+---------------
| Of course, it's hard to handle implementation-specific and
| user-defined declarations.
+---------------

Indeed! I was blithely ignoring that.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Lars Brinkhoff
Subject: Re: Handling declarations
Date: 
Message-ID: <85y7uc1156.fsf@junk.nocrew.org>
····@rpw3.org (Rob Warnock) writes:
> Lars Brinkhoff  <·········@nocrew.org> wrote:
> > ····@rpw3.org (Rob Warnock) writes:
> > > (defmacro my-let-if (condition bindings &body (forms decls))
> > >   (multiple-value-bind (binding-decls other-decls)
> > >       (split-decls bindings decls)
> > >     `(if ,condition
> > >        (let ,bindings ,@binding-decls ,@other-decls ,@forms)
> > >        (locally ,@other-decls ,@forms))))
> > >
> > > where SPLIT-DECLS is left as an exercise for the reader.  ;-}  ;-}
> > 
> > ...it was really this SPLIT-DECLS I was hoping to read more about.
>
> Well, it seemed sort of obvious, but I was in a rush [and don't
> need it myself], so I waved the "exercise for the reader" magic wand.  ;-}
> Basically, I supposed that SPLIT-DECLS would trundle down the list
> of DECLS looking for any that applied to (MAPCAR #'CAR BINDINGS),
> and separate those out.

I was hoping this would be more of a solved problem, and some people
would pop up and say "sure, we did this all the time on the LispM,
here's how...".

I believe the issue of proper declaration handling comes up
occasionally when writing macros.  It seems to me that Common Lisp is
carefully designed to allow declarations wherever useful, and I think
it's a shame to thoughtlessly break that property in user-written
extensions.  Unfortunately, there seems to be little interest in this.

> > Though actually, I think getting all declarations relating to some
> > specific variable (or list of variables) might be more useful.
>
> If you do that sort of thing often, then this is certainly
> the sort of routine you would want to have around.  ;-}

This would be my suggested syntax (for which I have an implementation):

  (defmacro my-let-if (condition bindings &body decls-and-forms)
    (let ((vars (bindings-variables bindings)))
      (with-parsed-body (:forms forms
                         :variable-declarations (:for vars :in var-decls)
                         :other-declarations other-decls)
                        decls-and-forms
        `(if ,condition
             (let ,bindings ,@var-decls ,@other-decls ,@forms)
             (locally ,@other-decls ,@forms)))))
From: Nathan Baum
Subject: Re: Handling declarations
Date: 
Message-ID: <Pine.LNX.4.64.0607280747450.2160@localhost>
On Fri, 28 Jul 2006, Lars Brinkhoff wrote:

> Kent M Pitman <······@nhplace.com> writes:
>> you might have a construct like
>>
>>  (defmacro my-let-if (condition bindings &body forms)
>>    `(if ,condition
>>         (let ,bindings ,@forms)
>          (locally ,@forms)))           ;slight alteration
>
> How do experienced Lispers write macros such as this to handle
> declarations in the body?  I.e. if FORMS has any declarations for
> variables in BINDINGS, you would like to include those in the body of
> LET, but not in LOCALLY.

Since declarations can only appear at the start of an implicit progn, we 
can simply discard everything before the first form which isn't a (declare 
...).

(defun strip-declares (forms)
   (nthcdr (position 'declare forms
                     :key #'(lambda (x) (and (consp x) (car x)))
                     :test (complement #'eq))
           forms))

(defmacro my-let-if (condition bindings &body forms)
   `(if ,condition
        (let ,bindings ,@forms)
        (locally ,@(strip-declares forms))))

> (Please disregard any problems with using lexical bindings in this
> particular example.)
From: Lars Brinkhoff
Subject: Re: Handling declarations
Date: 
Message-ID: <85wt9yp2m2.fsf@junk.nocrew.org>
Nathan Baum <···········@btinternet.com> writes:
> Since declarations can only appear at the start of an implicit
> progn, we can simply discard everything before the first form which
> isn't a (declare ...).

No, because there can be other declarations which may be desirable to
keep.
From: Lars Brinkhoff
Subject: Re: Handling declarations
Date: 
Message-ID: <85slkmp23z.fsf@junk.nocrew.org>
> Nathan Baum <···········@btinternet.com> writes:
>> Since declarations can only appear at the start of an implicit
>> progn, we can simply discard everything before the first form which
>> isn't a (declare ...).
> No, because there can be other declarations which may be desirable to
> keep.

For example, you probably don't want to discard those mentioned in
http://clhs.lisp.se/Body/03_ca.htm
From: Mark Carter
Subject: Re: Newbie macro puzzle
Date: 
Message-ID: <44c9ed08$0$15782$14726298@news.sunsite.dk>
Lars Brinkhoff wrote:

> That looks like PROGV, but keep in mind it does special bindings.

Bingo - that's what I wanted!

What I'm discovering is that with Lisp, it's in there somewhere, it's 
just a question of finding it. It's a process of learning - lots and 
lots of learning.

It may interest people to know that what I'm actually doing is trying an 
experiment in translating a piece of VBA code to Lisp. One thing that 
the code does is do lots of mechanical fetching of values - something 
that I think can be done behind the scenes by looking at the schema and 
delivering them pre-packaged to a calculation function. It's an approach 
that should drastically reduce the line-count of the program.

Another place that I foresee a great deal of tidying up is in the 
solution of some simultaneous equations. Currently, the VBA code has to 
pass in loads of hooks so that the equation solver can obtain the 
parameters for the equation. I looked at this recently, and it is a big 
hariy mess. I mean really horrendous to puzzle out. I'm figuring that 
with Lisp closures, basically all of the mess will go away.

My experiment continues.