From: Bruce R. Miller
Subject: Style Q's for numeric computing
Date: 
Message-ID: <2908207838@ARTEMIS.cam.nist.gov>
As a sort of diversion from programming toys, Lispview and abuse of
symbols, here's a bit of a different sort of symbol abuse;

I'm developing (accreting as needed, actually) a library of numeric
code.  Lisp's model of numbers is usually a boon, but sometimes a bane.

Particularly, you can almost always write things in a generic way.
Want half of x? write (/ x 2).  If x is double precision, you get
full precision, no problem.  

Well, there  is  a  problem  with  efficiency.   Even  with genera which
doesn't care  about  declarations,  you  win  by  writing  (* x 0.5) for
single and (* x 0.5d0) for double.  And in other Lisps (apparently)  you
win  greatly  by  including  appropriate  very  specific   declarations.
Likewise, you dont want to introduce a double precision value for pi  if
the arguments are single precision.

My basic outline for a user-level numeric function is basically as
follows. 
   a) check for special cases.
   b) convert complex computations to appropriate real when possible
   c) branch the real computation to single or double precision routines.

A minor headache is to deal with special cases before branching to
single/double.  So maybe I want to return pi, but I have to return the
`right' one  (ie. single or double prec).

But my  question  today  is  about  the  following:  The code to compute
single or double is the same  except that various constants are  changed
eg 1.0  vs  1.0d0,  0.5  vs  0.5d0,  and,  more  important, single-.. vs
double-float-epsilon.

I want to write the body ONCE and have two functions generated, one  for
single and one for double precision.  This minimizes writing, keeps  the
algorithms in sync, etc.

Here's a macro that would do this

(defmacro def-numeric (name lambda-list parameter-list &body body)
  (let ((single-name (intern (string-append name "-SINGLE")))
	(double-name (intern (string-append name "-DOUBLE")))
	(s-parms (loop for (s sv) in parameter-list
		       collecting (list s sv)))
	(d-parms (loop for (s nil dv) in parameter-list
		       collecting (list s dv))))
    `(progn
	<declarations so editor knows where these really are>
       (defun ,single-name ,lambda-list
	 (clos:symbol-macrolet ,s-parms
	   ,@body))
       (defun ,double-name ,lambda-list
	 (clos:symbol-macrolet ,d-parms
	   ,@body)))))

;Random example usage:
(def-numeric foo (a b)
	     ((half 0.5 0.5d0)
	      (eps single-float-epsilon double-float-epsilon))
  (if (> (abs a) eps)
      (* half (+ a b))
      (-  b)))

Ok, simple enough and it works.  The parameter-list is kinda ugly, but
allows random constants to be introduced and used.

It uses a defn from CLOS which is somewhat out of place (is
symbol-macrolet going to be in the real CL?) 

An alternate scheme might be like the following.  For each version,
define a local macro (macro-let), say the single prec version might be:
  (macrolet ((nfloat (x)
	       (cond ((numberp x)(float x 0.0))
	             ((eq x 'epsilon) single-float-epsilon)
		     (t x))))
	...

;Then you'd write
(def-numeric foo (a b)
  (if (> (abs a) (nfloat epsilon))
      (* (nfloat 1/2) (+ a b))
      (-  b)))

Perhaps slightly preferable?   Short of a macro which somehow `knows'
what I want coerced and what should stay integer/rational, that is. 

[As a side issue, although I'm writing for genera right now, if I wanted
to port the code to a unix box, I'd also want to add a zillion
declarations.  This hypothetical macro should also help with that!]

So, friends, whadya think?  Which do you prefer?
Am I missing some other grand scheme for doing this stuff? 
Any other stylistic comments?

From: Barry Margolin
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <kqrjtmINNmfq@early-bird.think.com>
I think both your versions are pretty reasonable.  All decent CL
implementations support CLOS these days, so they should have
SYMBOL-MACROLET.  Any that doesn't probably won't implement many of the
optimizations you're hoping to get from all your declarations.

But you could probably get away with just using LET instead of
SYMBOL-MACROLET or MACROLET.  The values you're binding to are constants,
and good compilers will notice that you never modify the variables so they
can propogate the constant value through the function body.  (One problem
with this is that Lucid doesn't actually declare the *-FLOAT-EPSILON
variables to be constant, so it doesn't work for this, but it works for
PI).

-- 
Barry Margolin
System Manager, Thinking Machines Corp.

······@think.com          {uunet,harvard}!think!barmar
From: Rob MacLachlan
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <1992Feb28.061843.54351@cs.cmu.edu>
In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:

>Lisp's model of numbers is usually a boon, but sometimes a bane.

Yes, though having a compiler that does type inference helps.  Float arithmetic
is more tractable than integer arithmetic, since the result of a float
operation is always a float.

>
>Particularly, you can almost always write things in a generic way.
>Want half of x? write (/ x 2).  If x is double precision, you get
>full precision, no problem.  
>
>Well, there  is  a  problem  with  efficiency.   Even  with genera which
>doesn't care  about  declarations,  you  win  by  writing  (* x 0.5) for
>single and (* x 0.5d0) for double.

Is the problem with doing an integer/float operation, or divide v.s. multiply?
Python (the CMU CL compiler) will convert (/ single-float 2) to 
(/ single-float 2.0), etc.  It does not currently convert division by a
constant to multiplication by the reciprocal (I don't know if it is a
numerically sound transformation.)

>And in other Lisps (apparently) you win greatly by including appropriate very
>specific declarations.

Well, you need to know what inputs to the expression are floats in which
format.  This is generally done by declaring function return values and some
variables (or all, depending on compiler stupidity) to be SINGLE-FLOAT or
DOUBLE-FLOAT.

It is also very important to declare float array types, such as:
    (declare (type (simple-array single-float (512 1024)) foo))

Declaring constant dimensions is a big help with multi-dimensional arrays,
since it allows multiplies to be converted to shift+add.

>Likewise, you dont want to introduce a double precision value for pi  if
>the arguments are single precision.

Actually, I suspect that in most conventional h/w Lisps, there is relatively
little advantage to carrying through computations in single precision.
Although double-precision float operations are somewhat slower, Lisp float
code generation is generally not good enough that the FPU stays terribly
busy.  You can save some space by converting everything to double, and then
coerce it back (assuming coercion hasn't been pessimized.)  Some FPUs do all
operations in extended precision anyway.

Probably the reason you see a big difference between SP and DP arithmetic on
Lispm's is that a single-float is immediate; doubles are heap allocated and
have to be GC'd.  With a good stock compiler, both SP and DP values will be
kept in registers whenever possible (giving little difference), and when they
must be tagged, they both must be heap allocated on a 32bit machine (also
giving little difference here.)

>I want to write the body ONCE and have two functions generated, one  for
>single and one for double precision.

[first example deleted.]

>(def-numeric foo (a b)
>  (if (> (abs a) (nfloat epsilon))
>      (* (nfloat 1/2) (+ a b))
>      (-  b)))

I prefer this, perhaps because it is more like a simpler approach that can
be be used with Python:

(declaim (inline foo float-epsilon))
(defun float-epsilon (x)
  (if (typep x 'double-float)
      double-float-epsilon
      single-float-epsilon))

(defun foo (a b)
  (if (> (abs a) (float-epsilon a))
      (* (float 1/2 a) (+ a b))
      (- b)))

Assuming the type of A is known at compile-time in the (foo A ...) call, the
result will be equivalent to your macro.  I'm not saying that writing helper
macros is a bad idea, but the optimizations that your proposed macros do are
enough like what the compiler ought to do that a good implementation could
make them largely unnecessary.

Another important point is that doing a call to a float function will
probably have substantial number-consing overhead.  This can be avoided in
implementations that do reasonable block compilation or inline expansion.
Minimizing number consing is the key to reasonable float performance on
stock h/w.  In addition to the allocation and GC overhead, there are all
those wasted cycles shuffling words between the FPU and memory, cache
misses, etc.  The % of number operations involving number-consing has to be
very low in order for you to be spending most of the time doing float
operations.

>[As a side issue, although I'm writing for genera right now, if I wanted
>to port the code to a unix box, I'd also want to add a zillion
>declarations.  This hypothetical macro should also help with that!]

It could, though the trivially added type declarations could often be
trivially inferred.

> (is symbol-macrolet going to be in the real CL?) 
Yes.

Rob MacLachlan (···@cs.cmu.edu)
From: Bruce R. Miller
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <2908293714@ARTEMIS.cam.nist.gov>
In article <······················@cs.cmu.edu>, Rob MacLachlan writes:
> In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:
>> Particularly, you can almost always write things in a generic way.
>> Want half of x? write (/ x 2).  If x is double precision, you get
>> full precision, no problem.  
>>...
> Is the problem with doing an integer/float operation, or divide v.s. multiply?

Both, really; For x in double precision, genera (8.1 on XL1200) shows
these to be progressively faster:
   (/ x 2) (* x 0.5) (* x 0.5d0)

> Python (the CMU CL compiler) will convert (/ single-float 2) to 
> (/ single-float 2.0), etc.  It does not currently convert division by a
> constant to multiplication by the reciprocal (I don't know if it is a
> numerically sound transformation.)

They shouldn't really differ more than the appropriate epsilon, should they?

> ...
>Probably the reason you see a big difference between SP and DP arithmetic on
> Lispm's is that a single-float is immediate; doubles are heap allocated and
> have to be GC'd.  With a good stock compiler, both SP and DP values will be
> kept in registers whenever possible (giving little difference), and when they

"Registers"?  What's that?  :>

> must be tagged, they both must be heap allocated on a 32bit machine (also
> giving little difference here.)

Perhaps you're right;  But wouldn't the DP excercize the GC more? (even
ephemeral).

> I prefer this, perhaps because it is more like a simpler approach that can
> be be used with Python:
> 
> (declaim (inline foo float-epsilon))
> (defun float-epsilon (x)
>   (if (typep x 'double-float)
>       double-float-epsilon
>       single-float-epsilon))
> (defun foo (a b)
>   (if (> (abs a) (float-epsilon a))
>       (* (float 1/2 a) (+ a b))
>       (- b)))
>Assuming the type of A is known at compile-time in the (foo A ...) call, the
>result will be equivalent to your macro.  I'm not saying that writing helper
>macros is a bad idea, but the optimizations that your proposed macros do are
>enough like what the compiler ought to do that a good implementation could
>make them largely unnecessary.

Well, granted that Symbolics compiler doesn't do quite as much as one
might expect it to do...
I suppose that for Python, one might simply have the macro define the
two functions, one with the declaration that the args are double, the
other single, and Python would do the rest?  Sounds nice!

> Another important point is that doing a call to a float function will
> probably have substantial number-consing overhead.  

In my macro, the float gets called at compile time.

> Rob MacLachlan (···@cs.cmu.edu)

thanks for the input.

.
.
.
.
.
.
.
From: Rob MacLachlan
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <1992Feb29.061343.207151@cs.cmu.edu>
In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:

>> It does not currently convert division by a constant to multiplication by
>> the reciprocal (I don't know if it is a numerically sound transformation.)
>
>They shouldn't really differ more than the appropriate epsilon, should they?

Beats me.  I'm just very cautious about doing float transformations simply
because they seem mathematically reasonable.  I did think of one problem: if
the constant is a denorm, then taking the reciprocal could overflow.  But
that's easy enough to handle.

>> On a 32bit machine [both SP and DP] values must be heap allocated (also
>> giving little difference here.)
>
>Perhaps you're right;  But wouldn't the DP excercize the GC more? (even
>ephemeral).

Yes, it will probably make a 2x difference in consing to use DP rather than
SP.  But that is smaller than the infinite difference between consing and
no-consing on the Lispm.  And if DP values are only used internally in the
function for expression temporaries, etc., then no DP values will be consed.


>> I prefer this, perhaps because it is more like a simpler approach that can
>> be be used with Python:
>> 
>> (declaim (inline foo float-epsilon))
[...]
>I suppose that for Python, one might simply have the macro define the
>two functions, one with the declaration that the args are double, the
>other single, and Python would do the rest?  Sounds nice!

Yes, you could do that.

>
>> Another important point is that doing a call to a float function will
>> probably have substantial number-consing overhead.  
>
>In my macro, the float gets called at compile time.

Not what I meant.  The call to FLOAT would be constant-folded as long as the
types are known.  The problem is that when doing a full function call to any
function, all arguments and return values must be tagged, and thus must be
heap-consed.  So if you are doing normal function calls to simple utility
functions in your inner loops, that will cause a lot of spurious consing.
Python offers a partial solution in that the block-compilation & inline
expansion mechanism allows the creation of a local copy of the utility
function which can be called using a non-consing calling function.

  Rob
From: Christopher McConnell
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <CCM.92Feb28141537@HITECH.CHESS.CS.CMU.EDU>
To solve similar problems I wrote these routines in the past.  What
they let you do is write generic code bodies that get expanded into
a huge mound of declared and customized bits of code.

    (auto-types
     (cases 
      ((time-average nil t) (type :zero :general))
      #'(lambda (unit)
	  ($case time-average
		 (nil (sum-inputs unit))
		 (t (time-averaged-sum-inputs unit)))
	  (let ((input (max min-in (min max-in (unit-net-input unit)))))
	    (setf 
	     (unit-state unit)
	     ($case 
	      type
	      (:zero (/ max-out (+ ($coerce 1.0) (exp (- input)))))
	      (:general 
	       (+ max-out 
		  (/ range (+ ($coerce 1.0) (exp (- input))))))))))))))


;;;%Cases
(defvar *CASES* nil "T when in a cases form.")
(defvar *CASE-WALKER* 'case-walker
  "Walker used in CASES form.")
(defvar *CASE-ENVIRONMENTS* '(cases cases-progn auto-types)
  "List of binding environments for cases stuff.")
(defvar *CASE-MACROS* nil
  "List of macros that get expanded in a CASES environment.")

;;;
(defmacro DEFCASEM (name args &body body)
  "Define a macro that gets expanded in a CASES environment."
  `(progn
     (pushnew ',name *case-macros*)
     (defmacro ,name ,args ,@body)))

;;;
(defun EXPAND-CASE-MACROS (form env)
  "Expand all of the case macros in FORM unless a binding environment
is encountered."
  (if (listp form)
      (if (member (first form) *case-macros*)
	  (expand-case-macros (macroexpand form env) env)
	  (if (member (first form) *case-environments*)
	      form
	      (mapcar #'(lambda (form)
			  (expand-case-macros form env))
		      form)))
      form))

;;;
(defun CASE-WALKER (form context env)
  (declare (ignore context env))
  (if (and (listp form)
	   (symbolp (first form)))
      (multiple-value-bind (form expanded)
	  (macroexpand-1 form env)
	(if expanded
	    (expand-case-macros form env)
	    form))
      form))

;;;
(defun BIND-VARIABLE (variable-and-bindings
		      bindings)
  "Bind variable to each of its bindings."
  (unless (= (length variable-and-bindings) 1)
    (let ((variable (first variable-and-bindings))
	  (value (first (cdr variable-and-bindings))))
      (append
       (if bindings
	   (mapcar 
	    #'(lambda (other-bindings)
		(cons
		 (list variable `',value)
		 other-bindings))
	    bindings)
	   (list (list (list variable `',value))))
       (bind-variable
	(cons variable (cddr variable-and-bindings))
	bindings)))))

;;;
(defun BINDING-PERMUTATIONS (variables-and-bindings
			     &optional (bindings nil))
  "Generate all of the possible bindings for all variables.
VARIABLES-AND-BINDINGS is ((var1 bind1 bind2 ...) ...)."
  (let* ((entry (first variables-and-bindings)))
    (if (null entry)
	bindings
	(binding-permutations 
	 (cdr variables-and-bindings)
	 (bind-variable entry bindings)))))

;;;
(defun TREE-REMOVE (atom tree)
  "Remove ATOM from tree."
  (if (atom tree)
      (unless (eq tree atom)
	(list tree))
      (list (mapcan #'(lambda (form)
			(tree-remove atom form))
		    tree))))

;;;
(defcasem $BINDING (symbol)
  "Cases macro that replaces the $BINDING form by the compile time
binding of SYMBOL."
  (if *cases*
      (symbol-value symbol)
      (error "$BINDING is only allowed inside of a CASES macro.")))  

;;;
(defcasem $COND (&rest clauses)
  "Cases macro that replaces the entire $COND by the body of the
first clause (test &rest body) that is non-nil at compile time based
on the bindings generated by a cases macro."
  (if *cases*
      (dolist (clause clauses '.no-code.)
	(when (eval (first clause))
	  (return `(progn ,@(cdr clause)))))
      (error "$COND is only allowed inside of a CASES macro.")))

;;;
(defmacro $CASE (switch &rest clauses)
  "Cases macro that replaces the entire $CASE by the body of the
first clause (value &rest body) that is matches the compile time
bindings for SWITCH generated by a cases macro.  The clause (otherwise
&rest body) matches if no other clause does."
  (if *cases*
      (dolist (clause clauses '.no-code.)
	(when (or (eq (first clause) 'otherwise)
		  (eval `(eql ,switch ',(first clause))))
	  (return `(progn ,@(cdr clause)))))
      (error "$CASE is only allowed inside of a CASES macro.")))

;;;
(defun GENERATE-CASES-BODY (bindings body env)
  "Generate BODY when the variables in BINDINGS are bound at compile
time." 
  (eval
   `(let ((*cases* t)
	  ,@bindings)
      (declare (special ,@(mapcar #'first bindings)))
      (tree-remove
       '.no-code. 
       (walker:walk-form (expand-case-macros ',body ',env)
			 ',env *case-walker*)))))

;;;
(defmacro CASES (variables-and-choices &body body &environment env)
  "Generate a clause for each possible set of variable bindings.
VARIABLES-AND-CHOICES is ((variable binding1 binding2 ...) ...).
BODY is present in each clause, but inside the body, compiler macros
such as $cond and $case are replaced at compile time by their matching
clauses.  When executed, the clause with the same bindings at run time
as at compile time will be run."
  (setq body `(progn ,@body))
  `(cond
     ,@(mapcar 
	#'(lambda (bindings)
	    `((and ,@(mapcar 
		      #'(lambda (binding) `(eql ,@binding))
		      bindings))
	      ,@(generate-cases-body bindings body env)))
	(binding-permutations variables-and-choices))))

;;;
(defmacro CASES-PROGN (variables-and-choices form &environment env)
  "Generate a clause for each possible set of variable bindings.
VARIABLES-AND-CHOICES is ((variable binding1 binding2 ...) ...).
FORM is present in each clause, but inside the form, compiler macros
such as $cond and $case are replaced at compile time by their matching
clauses."  
  `(progn ,@(mapcan #'(lambda (binding)
			(generate-cases-body binding form env))
		    (binding-permutations variables-and-choices))))

;;;%Numeric types
(defconstant NUMERIC-TYPES '(short-float float)
  "List of numeric types to be used in YANNS routines.")
(defsetting *NUMBER-TYPE* 'float (select-one-of numeric-types)
	    "The current type of numbers being used.")

;;;
(defmacro FIXNUM-TO-FLOAT (fixnum)
  "Convert FIXNUM to a float."
  `(the float 
	(* (the fixnum ,fixnum) (the float fixnum-float-conversion))))

;;;
(defmacro FLOAT-TO-FIXNUM (float)
  "Convert FLOAT to a fixnum."
  `(the fixnum
	(round (the float 
		    (* (the float ,float ) 
		       (the float float-fixnum-conversion))))))

;;;
(defun COERCE-TO-TYPE (number)
  "Coerce a number to the current type."
  (coerce number *number-type*))

;;;%%Auto-type functions
(defvar *AUTO-TYPE-FUNCTIONS* nil
  "List of numeric functions that automatically generate types in
auto-types forms.")

;;;
(defun ADD-AUTO-TYPE-FUNCTIONS (functions)
  "Add new math functions to have automatic type declarations in
on-types forms."
  (mapc #'(lambda (function)
	    (pushnew function *auto-type-functions*))
	functions))

;;;
(defun DELETE-AUTO-TYPE-FUNCTIONS (functions)
  "Delete math functions that have automatic type declarations in
auto-types forms."
  (setq *auto-type-functions* 
	(set-difference *auto-type-functions* functions)))
(add-auto-type-functions '(+ - * / sqrt exp log expt incf decf))

;;;%%Compiler macros
(defcasem $TYPE ()
  "Auto-types macro to substitute the current type for $TYPE."
  (or (and *cases* *number-type*)
      (error "$TYPE can only be used inside an auto-types macro.")))

;;;
(defcasem $COERCE (constant)
  "Auto-types macro to coerce CONSTANT to the current type in an
auto-types form." 
  (if *cases*
      (coerce-to-type constant)
      (error "$COERCE can only be used inside an auto-types form.")))

;;;
(defcasem $NUMBER-TYPE (&rest clauses)
  "Auto-types macro that replaces $NUMBER-TYPE by the body of the
first (type body) clause that is a supertype of the compile-time setting of
*NUMBER-TYPE*."
  `($cond (mapcar #'(lambda (clause)
		      `((subtypep *number-type* ',(first clause))
			,@(cdr clause)))
		  clauses)))

;;;%%Auto-walker
(defun AUTO-WALKER (form context environment)
  "Function to automatically generate type declarations for math
functions using the code walker."
  (declare (ignore context))
  (let ((function (when (and (listp form)
			     (symbolp (first form)))
		    (first form))))
    (cond ((eq function 'the)
	   (values (walker:walk-form form environment #'case-walker) t))
	  ((and function
		(not (macro-function function))
		(member function *auto-type-functions*))
	   (values
	    `(the ,*number-type* 
		  (,function 
		   ,@(mapcar 
		      #'(lambda (form)
			  (let ((new-form
				 (walker:walk-form form environment
						   'auto-walker)))
			    (if (or (and (listp new-form)
					 (eq (first new-form) 'the))
				    (numberp new-form))
				new-form
				`(the ,*number-type* ,new-form))))
		      (cdr form))))
	    t))
	  (t (case-walker form context environment)))))

;;;
(defmacro AUTO-TYPES (&body body &environment environment)
  "Generate a clause for each of NUMERIC-TYPES and select between them
at run-time based on *NUMBER-TYPE*.
Types will automatically be declared for math functions.  Define new
math functions by calling ADD-AUTO-TYPE-FUNCTIONS.  No types will be
substituted inside any form starting with the.
 ($type) will be replaced by the clauses type.  
 ($coerce constant) will coerce a constant to the current type.
 ($number-type (type1 body1) (type2 body2)) will substitute for the entire
macro the body of the first type clause where the type is a supertype
of the type being generated."
  (let ((*case-walker* #'auto-walker))
    (macroexpand-1 `(cases ((*number-type* ,@numeric-types))
			   ,@body)
		   environment)))

-- 
Chris McConnell  
What one does not know is exactly what one needs, and what one does know
one cannot use. --Faust
From: Bruce R. Miller
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <2908548587@ARTEMIS.cam.nist.gov>
In article <·················@taunton.crl.dec.com>, Bob Kerns writes:
> Bug here.  Any use of INTERN like this is asking for
> trouble. 

I thought about this a bit more, and reallized that I really didn't need
to define functions at all.  More appropriate is just to define an
environment that branches to the appropriate version of the body
depending on the types of the selector-vars; something like

(defmacro with-auto-precision (selector-vars &body body) ...

And while I was thinking about it, Christopher's message showed up which
implemented a similar idea with an involved code walker.

In article <·················@HITECH.CHESS.CS.CMU.EDU>, Christopher McConnell writes:
> To solve similar problems I wrote these routines in the past.  ...

I also liked Bob's idea of the defined constants.

> You could extend this with:
> (define-numeric-constant epsilon single-float-epsilon double-float-epsilon)
> (define-numeric-constant pi (float pi 0.0) pi)

It seems only slightly perverse to have these expand into a defconstant
to define, eg, pi = single-float pi and store the two values for lookup
in a table.

So, when I refocused on the essential things, I ended up with something
much simpler than what I started out with:

(defvar *default-float-type* 0.0)

(defmacro gfloat (x &optional (other *default-float-type*))
  (let (entry)
    (cond ((numberp x)
	   (if (numberp other)
	       (float x other)
	       `(float ,x ,other)))
	  ((and (symbolp x)(setq entry (gethash x *numeric-constants*)))
	   (if (numberp other)
	       (etypecase other
		 (single-float (first entry))
		 (double-float (second entry)))
	       `(if (typep ,other 'single-float)
	            ,(first entry)
	            ,(second entry))))
	  (t `(float ,x ,other)))))

It's a macro, cause a) I want it to simplify at compile time (I could
write optimizers) and 
b) 'cause I want to write (gfloat pi), not (gfloat 'pi)

Now, gfloat (for generic-float) can be useful by itself, or 
with-auto-precision just has to bind *default-float-type* for
the compiler:

(defmacro with-auto-precision (selector-vars &body body)
  `(if (or ,@(mapcar #'(lambda (v) `(typep ,v 'double-float)) selector-vars))
       (compiler-let ((*default-float-type* 0.0d0))
	 ,@body)
       (compiler-let ((*default-float-type* 0.0))
	 ,@body)))

[Of course, when needed, this macro could evolve to include a code-walk
to add declarations or whatever]

Now, you can use
  pi   ->  a single-float constant
  (gfloat pi type)  -> to get appropriately typed value
  (with-auto-precision (..)
	 ... (gfloat pi) ..)  ->   to get both.

Macros are so seductive that we can hide all sorts of magic in them.
But I worry when my macros start to do too much counter-intuitive stuff.
I overload the meaning of the symbol "pi" a bit much, but that's ok. But
worse, it seems, is that the analogy with FLOAT has gotten so
stretched.  Joe Q. User knows that pi = 3.1415927 and gfloat _looks_
like a function (and sounds like float), so it is perverse that
(gfloat pi) -> 3.14..d0 (sometimes).
Besides, *default-float-type* isn't even a type!

Then, Mike McDonald suggested that COERCE is clearer than FLOAT.  Indeed,
to my tastes, the distinction between coercion and simply `float'ing
makes the `semantics' of an (otherwise identical)  (GCOERCE PI) reasonable
where (GFLOAT PI) is questionable.
So my current plan is like the above, but with gcoerce.
[and *default-float-type* -> 'single-float or 'double-float, etc...]
The evaluation semantics are still a bit odd, but I can live with it.

Thanks for all the comments -- and of course, if you have more I'm still
listening! ---  It's been interesting hearing your points of view on
style.
From: Bob Kerns
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <RWK.92Mar3090150@itasca.crl.dec.com>
In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:

   From: ······@FS1.cam.nist.gov (Bruce R. Miller)
   Date: 2 Mar 92 18:09:47 GMT

   I also liked Bob's idea of the defined constants.

   > You could extend this with:
   > (define-numeric-constant epsilon single-float-epsilon double-float-epsilon)
   > (define-numeric-constant pi (float pi 0.0) pi)

   It seems only slightly perverse to have these expand into a defconstant
   to define, eg, pi = single-float pi and store the two values for lookup
   in a table.

I'm not sure what you're really saying, but it's not legal to
redefine PI.  I don't see what the DEFCONSTANT will buy you,
anyway.

   So, when I refocused on the essential things, I ended up with something
   much simpler than what I started out with:

   (defvar *default-float-type* 0.0)

   (defmacro gfloat (x &optional (other *default-float-type*))
     (let (entry)
       (cond ((numberp x)
	      (if (numberp other)
		  (float x other)
		  `(float ,x ,other)))
	     ((and (symbolp x)(setq entry (gethash x *numeric-constants*)))
	      (if (numberp other)
		  (etypecase other
		    (single-float (first entry))
		    (double-float (second entry)))
		  `(if (typep ,other 'single-float)
		       ,(first entry)
		       ,(second entry))))
	     (t `(float ,x ,other)))))

   It's a macro, cause a) I want it to simplify at compile time (I could
   write optimizers) and 
   b) 'cause I want to write (gfloat pi), not (gfloat 'pi)

   Now, gfloat (for generic-float) can be useful by itself, or 
   with-auto-precision just has to bind *default-float-type* for
   the compiler:

   (defmacro with-auto-precision (selector-vars &body body)
     `(if (or ,@(mapcar #'(lambda (v) `(typep ,v 'double-float)) selector-vars))
	  (compiler-let ((*default-float-type* 0.0d0))
	    ,@body)
	  (compiler-let ((*default-float-type* 0.0))
	    ,@body)))

COMPILER-LET doesn't exist anymore; it's been removed from the
language.  Use MACROLET.

(defmacro default-float-type () 0.0)

(defmacro gfloat (x &optional (other '(default-float-type))) ...)

(defmacro with-auto-precision (selector-vars &body body)
  `(if (or ,@(mapcar #'(lambda (v) `(typep ,v 'double-float)) selector-vars))
	(macrolet ((default-float-type () 0.0d0))
	   ,@body)
	(macrolet ((default-float-type () 0.0))
	    ,@body)))
From: Bob Kerns
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <RWK.92Mar3090334@itasca.crl.dec.com>
[Sorry if this gets posted twice; I aborted while sending because
I noticed I had a bug.]

In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:

   From: ······@FS1.cam.nist.gov (Bruce R. Miller)
   Date: 2 Mar 92 18:09:47 GMT

   I also liked Bob's idea of the defined constants.

   > You could extend this with:
   > (define-numeric-constant epsilon single-float-epsilon double-float-epsilon)
   > (define-numeric-constant pi (float pi 0.0) pi)

   It seems only slightly perverse to have these expand into a defconstant
   to define, eg, pi = single-float pi and store the two values for lookup
   in a table.

I'm not sure what you're really saying, but it's not legal to
redefine PI.  I don't see what the DEFCONSTANT will buy you,
anyway.

   So, when I refocused on the essential things, I ended up with something
   much simpler than what I started out with:

   (defvar *default-float-type* 0.0)

   (defmacro gfloat (x &optional (other *default-float-type*))
     (let (entry)
       (cond ((numberp x)
	      (if (numberp other)
		  (float x other)
		  `(float ,x ,other)))
	     ((and (symbolp x)(setq entry (gethash x *numeric-constants*)))
	      (if (numberp other)
		  (etypecase other
		    (single-float (first entry))
		    (double-float (second entry)))
		  `(if (typep ,other 'single-float)
		       ,(first entry)
		       ,(second entry))))
	     (t `(float ,x ,other)))))

   It's a macro, cause a) I want it to simplify at compile time (I could
   write optimizers) and 
   b) 'cause I want to write (gfloat pi), not (gfloat 'pi)

   Now, gfloat (for generic-float) can be useful by itself, or 
   with-auto-precision just has to bind *default-float-type* for
   the compiler:

   (defmacro with-auto-precision (selector-vars &body body)
     `(if (or ,@(mapcar #'(lambda (v) `(typep ,v 'double-float)) selector-vars))
	  (compiler-let ((*default-float-type* 0.0d0))
	    ,@body)
	  (compiler-let ((*default-float-type* 0.0))
	    ,@body)))

COMPILER-LET doesn't exist anymore; it's been removed from the
language.  Use MACROLET.

(defmacro default-float-type () 0.0)

(defmacro gfloat (x &optional (other '(default-float-type)) &environment env)
   (setq other (macroexpand other env))  ;; So we can make expand-time decisions.
   ...)

(defmacro with-auto-precision (selector-vars &body body)
  `(if (or ,@(mapcar #'(lambda (v) `(typep ,v 'double-float)) selector-vars))
	(macrolet ((default-float-type () 0.0d0))
	   ,@body)
	(macrolet ((default-float-type () 0.0))
	    ,@body)))
From: Bob Kerns
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <RWK.92Feb28182328@taunton.crl.dec.com>
In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:

   Date: 27 Feb 92 19:30:38 GMT
   From: ······@FS1.cam.nist.gov (Bruce R. Miller)

   Here's a macro that would do this

   (defmacro def-numeric (name lambda-list parameter-list &body body)
     (let ((single-name (intern (string-append name "-SINGLE")))
	   (double-name (intern (string-append name "-DOUBLE")))

----------------
Bug here.  Any use of INTERN like this is asking for
trouble.  This can cause symbol conflicts between packages,
or between different user functions, etc. etc.  Furthermore,
you've just given up any explicit control over what package
these symbols get created in.  If your DEF-NUMERIC form is
read with *PACKAGE* bound to one thing, and then this is
evaluated with it bound to something else, you won't get
what you expect!

The usual "fix" for the second problem is to intern in the
same package as the original symbol, but this makes the
first problem much much worse.

The best route is to name both functions being created.
(defmacro def-numeric-function (single-name double-name lambda-list
				parameter-list &body body)
   ...)

An alternative is to maintain an explicit table mapping
from "numfun" FOO to the two uninterned functions that
implement it, but it's difficult (but not impossible)
to do this without paying a runtime cost.  You'd end up
with something like this:

...
  (defun ,name (type &rest args)
     (apply (lookup-numfun ',name type) args))
  (define-compiler-optimizer ,name (type &rest args)
     ;; Need to check for TYPE being constant, actually.
     `(funcall (load-time-value (lookup-numfun ',',name ',type)) ,@args))
  (defun ,single-name-gensymbol ,@arglist (macrolet # ,@body))
  (add-numfun ',name #',single-name-gensymbol 'single)
----------------

	   (s-parms (loop for (s sv) in parameter-list
			  collecting (list s sv)))
	   (d-parms (loop for (s nil dv) in parameter-list
			  collecting (list s dv))))
       `(progn
	   <declarations so editor knows where these really are>
	  (defun ,single-name ,lambda-list
	    (clos:symbol-macrolet ,s-parms
	      ,@body))
	  (defun ,double-name ,lambda-list
	    (clos:symbol-macrolet ,d-parms
	      ,@body)))))

   ;Random example usage:
   (def-numeric foo (a b)
		((half 0.5 0.5d0)
		 (eps single-float-epsilon double-float-epsilon))
     (if (> (abs a) eps)
	 (* half (+ a b))
	 (-  b)))

   Ok, simple enough and it works.  The parameter-list is kinda ugly, but
   allows random constants to be introduced and used.

I don't think it's too bad, actually.  It's probably the syntax
I would choose for this particular implementation approach.
It is consistent with all the rules I outline in my Macrology course
for how to design a macro parameter list.

   It uses a defn from CLOS which is somewhat out of place (is
   symbol-macrolet going to be in the real CL?) 

Yes.  You should immediately run out and buy a copy of
Common Lisp the Language Second Edition (CLtLII).  Really, Bruce,
I'm surprised at you!  ;=)

   An alternate scheme might be like the following.  For each version,
   define a local macro (macro-let), say the single prec version might be:
     (macrolet ((nfloat (x)
		  (cond ((numberp x)(float x 0.0))
			((eq x 'epsilon) single-float-epsilon)
			(t x))))

Probably that last clause should be
                        (t (float x 0.0)))
because you'd want to use this macro to coerce computed quantities
to the desired format, as well.
	   ...

   ;Then you'd write
   (def-numeric foo (a b)
     (if (> (abs a) (nfloat epsilon))
	 (* (nfloat 1/2) (+ a b))
	 (-  b)))

   Perhaps slightly preferable?   Short of a macro which somehow `knows'
   what I want coerced and what should stay integer/rational, that is. 

You could extend this with:

(define-numeric-constant epsilon single-float-epsilon double-float-epsilon)
(define-numeric-constant pi (float pi 0.0) pi)

and then you can have all the named frobs you want.  This may come in
handy if you want to have varying cutoff points in numerical approximation
algorithms, for example.

   [As a side issue, although I'm writing for genera right now, if I wanted
   to port the code to a unix box, I'd also want to add a zillion
   declarations.  This hypothetical macro should also help with that!]

Indeed.  This sort of modularity is what macros are there
to help you acheive.

   So, friends, whadya think?  Which do you prefer?

I'm not going to state a preference, because I think it
will depend a bit on how you intend to use it.  In a way,
this is like asking "which is better, LET or DEFCONSTANT?".
They don't do the same things.

Offhand, I would more expect to encounter situations in which
the second choice would be more apropriate.

   Am I missing some other grand scheme for doing this stuff? 
   Any other stylistic comments?

I'm not really a big fan of SYMBOL-MACROLET, but this is
about as legitimate a usage of it as you'll find.
From: Bruce R. Miller
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <2908294433@ARTEMIS.cam.nist.gov>
In article <·················@taunton.crl.dec.com>, Bob Kerns writes:
> In article <··········@ARTEMIS.cam.nist.gov> ······@FS1.cam.nist.gov (Bruce R. Miller) writes:
>    (defmacro def-numeric (name lambda-list parameter-list &body body)
>      (let ((single-name (intern (string-append name "-SINGLE")))
> 	   (double-name (intern (string-append name "-DOUBLE")))
> ----------------
> Bug here.  Any use of INTERN like this is asking for
> trouble.  This can cause symbol conflicts between packages,
> or between different user functions, etc. etc.  Furthermore,
> you've just given up any explicit control over what package
> these symbols get created in.  If your DEF-NUMERIC form is
> read with *PACKAGE* bound to one thing, and then this is
> evaluated with it bound to something else, you won't get
> what you expect!

Hmm, you're right, of course, but the way I intended to use it, it's not
quite as bad as you imply;

I had intended def-numeric, foo-single & foo-double to all be
non-exported symbols in the package, say, NUMERIC.  Some other exported
function would do the branching.  But still...

That suggests a further improvement actually;  If a mung the lambda-list
clos-style to indicate which vars determine the branching, I could just
go ahead and define a function called name which does the branching
itself and avoid the -single, -double names altogether.

>    It uses a defn from CLOS which is somewhat out of place (is
>    symbol-macrolet going to be in the real CL?) 
> 
> Yes.  You should immediately run out and buy a copy of
> Common Lisp the Language Second Edition (CLtLII).  Really, Bruce,
> I'm surprised at you!  ;=)

Mea culpa :<  I keep waiting for CLtLIII!!!

> You could extend this with:
>  (define-numeric-constant epsilon single-float-epsilon double-float-epsilon) 
>  (define-numeric-constant pi (float pi 0.0) pi)
> and then you can have all the named frobs you want.  

and use compile-time lookup instead of a ever growing COND in the macro.
Yes!


and again, thanks
From: Mike McDonald
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <1992Feb29.023028.15158@mlb.semi.harris.com>
In article <·················@taunton.crl.dec.com>, ···@taunton.crl.dec.com (Bob Kerns) writes:
|>    An alternate scheme might be like the following.  For each version,
|>    define a local macro (macro-let), say the single prec version might be:
|>      (macrolet ((nfloat (x)
|> 		  (cond ((numberp x)(float x 0.0))
|> 			((eq x 'epsilon) single-float-epsilon)
|> 			(t x))))
|> 
|> Probably that last clause should be
|>                         (t (float x 0.0)))
|> because you'd want to use this macro to coerce computed quantities
|> to the desired format, as well.
|> 	   ...

  I'm assuming that you want (float x 0.0) to coerce x to be a single-float. If
That's the case, this won't work all the time. If *read-default-float-format* is
set to something other than single-float, x will be coerced to that type. That's
the way I inturpret pg. 350 of CLtL2 anyway. Besides, isn't 
(coerce x 'single-float) clearer anyway?

  Mike McDonald				Advanced Technology Dept.	
					Harris Corp.
  Email: ···@trantor.harris-atd.com	M.S. 3A-1912
  Voice: (407) 727-5060			P.O. Box 37
  Fax:   (407) 729-3363			Melbourne, Florida 32902
From: Bob Kerns
Subject: Re: Style Q's for numeric computing
Date: 
Message-ID: <RWK.92Feb29204318@taunton.crl.dec.com>
In article <······················@mlb.semi.harris.com> ···@trantor.harris-atd.com (Mike McDonald) writes:

   Date: Sat, 29 Feb 1992 02:30:28 GMT
   From: ···@trantor.harris-atd.com (Mike McDonald)

   In article <·················@taunton.crl.dec.com>, ···@taunton.crl.dec.com (Bob Kerns) writes:
   |>    An alternate scheme might be like the following.  For each version,
   |>    define a local macro (macro-let), say the single prec version might be:
   |>      (macrolet ((nfloat (x)
   |> 		  (cond ((numberp x)(float x 0.0))
   |> 			((eq x 'epsilon) single-float-epsilon)
   |> 			(t x))))
   |> 
   |> Probably that last clause should be
   |>                         (t (float x 0.0)))
   |> because you'd want to use this macro to coerce computed quantities
   |> to the desired format, as well.
   |> 	   ...

     I'm assuming that you want (float x 0.0) to coerce x to be a single-float. If
   That's the case, this won't work all the time. If *read-default-float-format* is
   set to something other than single-float, x will be coerced to that type. That's
   the way I inturpret pg. 350 of CLtL2 anyway. 

This isn't a question of correctness, but only of style.

If you go and globally twiddle the variables so the reader does
funny things, you'll break *LOTS* of programs.  The language
you're then reading is something different from Common Lisp.
You could set *READTABLE* to something bizarre, too, after all.

In other words:  "If it hurts when you do that, Don't DO that, then!"
Don't globally set the reader or printer variables.  Or if you
do, don't complain that you can't correctly compile programs
written in Common Lisp.

One could also argue that writing 0.0 there is more correct
because if you set that variable you're trying to always use
that format instead of single.  So you could set it to short,
and your program would adapt.

   Besides, isn't (coerce x 'single-float) clearer anyway?

Absolutely.  And despite my remarks above, I have no objections
to writing your code to be defensive, if it also brings you
clarity!

I didn't change that because I didn't want to distract from
the main point with a style issue.