From: Michael Hudson
Subject: Questions of genericity from a newcomer
Date: 
Message-ID: <m3so2emv2k.fsf@atrus.jesus.cam.ac.uk>
Disclaimer 1: I'm pretty new to common lisp. I know scheme to some
degree, but it's rapidly becoming apparent that this isn't any more
helpful than already knowing C or Python, say. I have Graham's book on
order, but amazon.co.uk seem to be having arse<->elbow difficulties...

Disclaimer 2: This *is* for an assigned project; but my questions are
more about lisp than my project (my project doesn't have to be in
lisp but I've been meaning to learn it for ages).

To the point...

The project is about polynomials over finite fields. So I need data
structures for polynomials and for elements of finite fields.

So I have this:

(defstruct polynomial
  coeffs)

(defun add-polynomial (x y) ; is this good style? I don't know!
  (let ((a (polynomial-coeffs x))
        (b (polynomial-coeffs y)))
    (let ((prefix (loop until (or (null a) (null b))
                        collect (+ (car a) (car b))
                        do (setq a (cdr a))
                           (setq b (cdr b)))))
      (if (null a) (nconc prefix b) (nconc prefix a))
      (make-polynomial :coeffs prefix))))

and similar for multiplication, subtraction, etc.

Q1: is there any way I can arrange things for 

(+ f g)

to call add-polynomial if f and g are integers? I'm guessing not.

Q2: I'm testing this data structure using integer coefficients but
ultimately I'm going to want to use finite field elements. So is it
safe to add the coefficients using #'+?

Is it better practice to defstruct polynomial along the lines of
(actually what follows doesn't work; I hope the intent is clear)

(defstruct polynomial
  coeffs
  (adder #'+))

(defun add-polynomial (x y)
  (flet ((adder (polynomial-adder x)))
    (let ((a (polynomial-coeffs x))
          (b (polynomial-coeffs y)))
      (let ((prefix (loop until (or (null a) (null b))
                          collect (adder (car a) (car b))
                          do (setq a (cdr a))
                             (setq b (cdr b)))))
        (if (null a) (nconc prefix b) (nconc prefix a))
        (make-polynomial :coeffs prefix :adder #'adder)))))

? This could rapidly get tedious.

Am I right in thinking that defstruct has nothing to do with CLOS? If
so is there a more elegeant CLOS-y solution to my problems?

Be as offensive about my style as you like/can - I can brutally
transliterate C-style code to lisp, but I'd like to know how to do it
"properly".

Thanking you in advance, 
Michael

From: Shin
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <3829bc51.8491405@news.iddeo.es>
May I suggest some ideas:

First, it would be useful to add an slot to remember where the
coefficients of a polynomial live. If you are only interested in Z/pZ
then the prime will be enough. This way you will be able to operate
mod p inside your functions... do you need a test for prime numbers?

Second, the lispy way to define things like ADD-POLYNOMIAL is something
following this schema:

   (defun add-polynomial (&rest polynomials)
     (flet ((add-two-polynomials (p q)
              ;; Here it goes code to add two polynomials.
              ;; Perhaps MAPCAR and NTHCDR could give a
              ;; more compact loop, without LOOP, but I
              ;; don't know if it is worth changing.
              ;; Remember to check whether p and q have
              ;; their coeffs in the same field.
              ))
       (reduce #'add-two-polynomials polynomials)))

Check FLET and REDUCE in your favorite Lisp docs if you weren't aware of
them.

With this definition you can use that functions with an arbitrary number
of polynomials, as you do with numbers with +, say:

   ;;; Assuming p, q, r and s are polynomials

   (add-polynomial p q) ; OK
   (add-polynomial p q r) ; Also OK
   (add-polynomial p (add-polynomial q r p r) s) ; OK as well

As to the sum of numbers and polynomials question, you could behave
within add-two-polynomials according to the type of the input. You could
then find useful NUMBERP and the predicate POLYNOMIAL-P that Lisp
provide automatically when you define the polynomial structure.

This techniques would work similarly for the rest of operations as well.

Hope this helps,

-- Shin
From: Clemens Heitzinger
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <1e12rw9.1egd1mwdinynoN%cheitzin@ag.or.at>
Shin <···@retemail.es> wrote:

[...]
> With this definition you can use that functions with an arbitrary number
> of polynomials, as you do with numbers with +, say:
> 
>    ;;; Assuming p, q, r and s are polynomials
> 
>    (add-polynomial p q) ; OK
>    (add-polynomial p q r) ; Also OK
>    (add-polynomial p (add-polynomial q r p r) s) ; OK as well

Sorry about nit-picking...

imho the following should work as well:

(add-polynomials p) -> p
(add-polynomials) -> #<NULL-POLYNOMIAL>

Now what is this null polynomial?  Depends on your implementation and
the polynomial ring you work in.

-- 
Clemens Heitzinger
http://ag.or.at:8000/~clemens   (Lisp related material)
From: Michael Hudson
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <m366z9qh2m.fsf@atrus.jesus.cam.ac.uk>
········@ag.or.at (Clemens Heitzinger) writes:

> Shin <···@retemail.es> wrote:
> 
> [...]
> > With this definition you can use that functions with an arbitrary number
> > of polynomials, as you do with numbers with +, say:
> > 
> >    ;;; Assuming p, q, r and s are polynomials
> > 
> >    (add-polynomial p q) ; OK
> >    (add-polynomial p q r) ; Also OK
> >    (add-polynomial p (add-polynomial q r p r) s) ; OK as well
> 
> Sorry about nit-picking...
> 
> imho the following should work as well:
> 
> (add-polynomials p) -> p
> (add-polynomials) -> #<NULL-POLYNOMIAL>
> 
> Now what is this null polynomial?  Depends on your implementation and
> the polynomial ring you work in.

Yup, this had occured to me too. I think I can cope with pairwise
addition. I suppose one could make a generic zero polynomial that is a
member of all polynomial types, but that adds much complexity for
little gain.

Regards,
Michael
From: Clemens Heitzinger
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <1e14ejb.8the0tl88x1uN%cheitzin@ag.or.at>
Michael Hudson <·····@cam.ac.uk> wrote:

> ········@ag.or.at (Clemens Heitzinger) writes:
> > Now what is this null polynomial?  Depends on your implementation and
> > the polynomial ring you work in.
> 
> Yup, this had occured to me too. I think I can cope with pairwise
> addition. I suppose one could make a generic zero polynomial that is a
> member of all polynomial types, but that adds much complexity for
> little gain.

In my implementation a null polynomial is one with an empty list of
terms.

(defmethod null-polynomial-p ((p polynomial))
  (null (terms p)))

(defun make-null-polynomial ()
  (make-instance 'polynomial :terms nil))

Of course you can't decide which polynomial ring such a null polynomial
lies in.  -- I think it simplifies things; null-polynomial-p occurs
quite often in my code.

-- 
Clemens Heitzinger
http://ag.or.at:8000/~clemens   (Lisp related material)
From: Michael Hudson
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <m3puximuzc.fsf@atrus.jesus.cam.ac.uk>
Michael Hudson <·····@cam.ac.uk> writes:

> Q1: is there any way I can arrange things for 
> 
> (+ f g)
> 
> to call add-polynomial if f and g are integers? I'm guessing not.
> 
s/integers/polynomials/

*blush*
Michael
From: Barry Margolin
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <_BgW3.52$vE2.1833@burlma1-snr2>
In article <··············@atrus.jesus.cam.ac.uk>,
Michael Hudson  <·····@cam.ac.uk> wrote:
>Michael Hudson <·····@cam.ac.uk> writes:
>
>> Q1: is there any way I can arrange things for 
>> 
>> (+ f g)
>> 
>> to call add-polynomial if f and g are integers? I'm guessing not.
>> 
>s/integers/polynomials/

You could create your own package that shadows the + symbol and defines it
as a generic function that calls add-polynomial when the arguments are
polynomials, and COMMON-LISP:+ when the arguments are numbers:

(defpackage poly
  (:use COMMON-LISP)
  (:shadow +)
  ...)

(defmethod + ((p1 polynomial) (p2 polynomial))
  (add-polynomial p1 p2))

(defmethod + (x y)
  (common-lisp:+ x y))

However, you still won't be able to pass polynomials to other functions
that call the standard Common Lisp + function internally -- this change
only affects programs that use the POLY package.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, 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.
From: John Watton
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <80c0ju$tjp$1@nnrp1.deja.com>
In article <··············@atrus.jesus.cam.ac.uk>,
  Michael Hudson <·····@cam.ac.uk> wrote:
> Am I right in thinking that defstruct has nothing to do with CLOS? If
> so is there a more elegeant CLOS-y solution to my problems?
>
> Be as offensive about my style as you like/can - I can brutally
> transliterate C-style code to lisp, but I'd like to know how to do it
> "properly".

I would do something like:

(defclass polynomial ()
  ((coeffs :accessor polynomial-coeffs
	   :initarg :coeffs)))

(defmethod poly+ ((x polynomial) (y polynomial))
  (let* ((a (polynomial-coeffs x))
	 (b (polynomial-coeffs y))
	 (prefix (loop until (or (null a) (null b))
		     collect (+ (car a) (car b))
		     do (setq a (cdr a))
			(setq b (cdr b))))
	 (prefix (if (null a) (nconc prefix b) (nconc prefix a))))
    (make-instance 'polynomial :coeffs prefix)))

This works if the coeffs are lists of all numbers. You will need to
define how to add other types of coefficients yourself, probably inside
the poly+ method. There is never a free lunch. There is no advntage to
using + as your method name since it is not generic and you cannot use
it unless you want + to break everywhere else. You can use structures
(instead of classses) with CLOS and defmethod on them but it is not
recommended unless slot access efficiency becomes a problem.

--
John Watton
Alcoa Inc.


Sent via Deja.com http://www.deja.com/
Before you buy.
From: Robert Monfera
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <3829A31D.E518CEEF@fisec.com>
John Watton wrote:
 
> I would do something like:
> 
> (defclass polynomial ()
>   ((coeffs :accessor polynomial-coeffs
>            :initarg :coeffs)))
> 
> (defmethod poly+ ((x polynomial) (y polynomial))
>   (let* ((a (polynomial-coeffs x))
>          (b (polynomial-coeffs y))
>          (prefix (loop until (or (null a) (null b))
>                      collect (+ (car a) (car b))
>                      do (setq a (cdr a))
>                         (setq b (cdr b))))
>          (prefix (if (null a) (nconc prefix b) (nconc prefix a))))
>     (make-instance 'polynomial :coeffs prefix)))

Just to extend a bit on this recommendation from John: it also gives you
a tremendous amount of flexibility should you need to define different
poly+ methods for various classes of polynoms.  As you probably observed
in the frist line of the method definition, this method will be invoked
only if both x and y are polynomials.  If you have various types of
polynomials, you could write different methods on them - ythis way, you
can even add polynomials of different classes.

Also, if you add &rest other-polynomials, you can use a recursive
definition to allow the addition of an arbitrary number of polynomials.
Alternatively, you may use REDUCE.

To implement commutativity across classes, you could do this:

(defmethod poly+ ((x polynomial-A) (y polynomial-B) &rest others)
	[body of the method])

(defmethod poly+ ((x polynomial-B) (y polynomial-A) &rest others)
    (apply #'poly+ y x others))

Good luck with CLOS!
Robert
From: William Deakin
Subject: A potato answer to questions of genericity
Date: 
Message-ID: <382BFB73.C47552E8@pindar.com>
John Watton wrote:

> Michael Hudson <·····@cam.ac.uk> wrote:
> > Am I right in thinking that defstruct has nothing to do with CLOS? If
> > so is there a more elegeant CLOS-y solution to my problems?
>
> I would do something like: [elided as polynomial class definition]

Following on this, and something about potatoes I posted a while ago, here
is some code that does something like you want. This is a potato based and
is written by me, somebody who is by no means a Lisp expert, as I'm sure
that you will be aware if you have read any of my postings ;)

> This works if the coeffs are lists of all numbers.

This uses "dimensions" as a vector of numbers which is reasonably fast
implemention. It allows adding of potatoes to numbers and "overloads" the +
operator but only in the "GRATIN" package. It also does some awful pretty
printing.

It does have (potato (vector 1 4 2) "z") to give a pototo object: #<POTATO
1z^0+4z^1+xz^2>. To extend this for multiplication &c is not difficult.
Also, if two potatoes are added (+ #<POTATO 1z^0+4z^2> #<POTATO
2z^0-4z^2>)) there is a normalisation 3 is returned.

It also needs some reader hacking to get it take sensible input.

It also handles potatoes with different "names". For example:  (+ -4
(potato (vector 1 -4) "z") (potato (vector 1 4) "x")) gives #<POTATO
((-2z^0-4z^1)x^0+4x^1)>. This is achieved by applying an alphabetic
ordering on variable names.

Best Regards,

:) will

-----------------------------------------------------Cut
here-----------------------------------------------------
;;; -*- Mode: Lisp; Syntax: Common-Lisp; Package: COMMON-LISP-USER -*-
;;; Copyright William Deakin 1999.
;;; This code is provided as is and could be broken in lots of ways but
don't
;;; blame me. I'm not an expert. Do with it what you will. If you do find
it
;;; any use or needed to fix things, I would be interesting in any changes
you
;;; make. But this is a polite request and not binding or anything.

(defpackage :gratin
  (:use "COMMON-LISP")
  (:shadow +))

(in-package "GRATIN")

(defclass potato ()
  ((main-name  :initarg :name
               :accessor name
               :initform "x")
   (dimensions :initarg :dimensions
               :type vector
               :initform (vector 0)))
  (:documentation "A potato is a named vector of dimensions"))

(defmethod dimensions ((p potato))
  (copy-seq (slot-value p 'dimensions)))

(defmethod (setf dimensions) ((v vector) (p potato))
  (setf (slot-value p 'dimensions) v))

(defmethod dimension ((p potato) (i integer))
  (svref (slot-value p 'dimensions) i))

(defmethod (setf dimension) (value (p potato) (i integer))
  (setf (svref (slot-value (the potato p) 'dimensions) i) value))

(defmethod potato ((v vector) &optional (name nil))
  (if name (make-instance 'potato :dimensions v :name name)
    (make-instance 'potato :dimensions v)))

(defmethod copy ((p potato))
  (potato (dimensions p) (name p)))

(defmethod potato-p ((p potato))
  t)

(defmethod potato-p ((p t))
  nil)

(defmethod degree ((p number))
  0)

(defmethod degree ((p potato))
  (1- (length (dimensions (the potato p)))))

(defmethod normalise ((p potato))
  (let* ((q (dimensions p))
         (degree (position 0 q :test (complement #'eql)
                           :from-end t)))
    (cond ((null degree) (setf p 0))
          ((= degree 0)
           (setf p (normalise (dimension p 0))))
          ((< degree (degree p))
           (setf (dimensions p) (delete 0 q :start degree))))
    p))

(defmethod normalise ((p number))
  p)

(defmethod name= ((p potato) (q potato))
  (equal (name p) (name q)))

(defmethod name> ((p potato) (q potato))
  (string> (name p) (name q)))

(defgeneric add (p q)
  (:documentation "Addition"))

(defmethod add ((p number) (q number))
  (common-lisp:+ p q))

(defmethod add ((p potato) (q number))
  (add q p))

(defmethod add ((p number) (q potato))
  (let ((r (copy q)))
    (setf (dimension r 0) (add p (dimension r 0)))
    (normalise r)))

(defmethod add ((p potato) (q potato))
  (let ((r (copy p))
 (s (copy q)))
    (cond ((name= p q)
    (if (>= (degree r) (degree s)) (rotatef r s))
    (dotimes (i (1+ (degree s)))
      (setf (dimension r i)
     (add (dimension r i) (dimension s i)))))
   (t (if (name> r s) (rotatef r s))
      (setf (dimension r 0) (add (dimension r 0) s))))
    (normalise r)))

(defmethod + (&rest potatoes)
  (if (null potatoes) 0
    (reduce #'add potatoes)))

(defun sign-character (this)
  (cond ((zerop this) "")
        ((minusp this) "-")
        (t "+")))

(defun output-potato (this stream)
  (let ((lasti (degree this))
        (name (name this)))
    (dotimes (i (1+ lasti))
      (let ((this (dimension this i)))
        (if (numberp this)
            (unless (zerop this)
              (progn (format stream "~A" (sign-character this))
                     (format stream "~D~A^~D" (abs this) name i)))
   (progn (format stream "(")
                 (output-potato this stream)
                 (format stream ")~A^~D" name i)))))))

(defmethod print-object ((this potato) stream)
  (progn (format stream "#<POTATO (")
         (output-potato this stream)
         (format stream ")>")))
From: Clemens Heitzinger
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <1e12sbl.rkfuzy1h5667cN%cheitzin@ag.or.at>
Michael Hudson <·····@cam.ac.uk> wrote:

> The project is about polynomials over finite fields. So I need data
> structures for polynomials and for elements of finite fields.
> 
> So I have this:
> 
> (defstruct polynomial
>   coeffs)
> 
> (defun add-polynomial (x y) ; is this good style? I don't know!
>   (let ((a (polynomial-coeffs x))
>         (b (polynomial-coeffs y)))
>     (let ((prefix (loop until (or (null a) (null b))
>                         collect (+ (car a) (car b))
>                         do (setq a (cdr a))
>                            (setq b (cdr b)))))
>       (if (null a) (nconc prefix b) (nconc prefix a))
>       (make-polynomial :coeffs prefix))))

Since you store the coefficients in a list, I assume you are only
interested in univariate polynomial rings K[x], and not e.g. in
K[x,y,z].

I'd do something like

(defclass field (ring)
  ((division :accessor division :initarg :division)))

(defun make-rational-numbers ()
  (make-instance 'field
    :name "the rational numbers"
    :addition #'+ :subtraction #'- :negation #'- :multiplication #'*
:division #'/
    :same-p #'eql :zero-element 0 :unity-element 1))

and similarly for finite fields.

> Q2: I'm testing this data structure using integer coefficients but
> ultimately I'm going to want to use finite field elements. So is it
> safe to add the coefficients using #'+?

Of course this depends on the coefficient field.  I think the best way
is to that start with (rings or) fields (like above) and build the
polynomial ring from there.  You can choose the make the polynomials
remember over which field they are defined (ie, they have a slot which
contains that field), or you can go with something like

(defun add-polynomials (module term-ordering p1 p2)
   ...)

I don't know which approach is generally the best; this will probably
depend on your application.

> Is it better practice to defstruct polynomial along the lines of
> (actually what follows doesn't work; I hope the intent is clear)
> 
> (defstruct polynomial
>   coeffs
>   (adder #'+))
> 
> (defun add-polynomial (x y)
>   (flet ((adder (polynomial-adder x)))
>     (let ((a (polynomial-coeffs x))
>           (b (polynomial-coeffs y)))
>       (let ((prefix (loop until (or (null a) (null b))
>                           collect (adder (car a) (car b))
>                           do (setq a (cdr a))
>                              (setq b (cdr b)))))
>         (if (null a) (nconc prefix b) (nconc prefix a))
>         (make-polynomial :coeffs prefix :adder #'adder)))))
> 
> ? This could rapidly get tedious.
> 
> Am I right in thinking that defstruct has nothing to do with CLOS? If
Yes.

> so is there a more elegeant CLOS-y solution to my problems?

Well, I have an implementation which starts with monomials and terms and
stores the coefficient as a list of terms (see outline below).  Addition
etc of polynomials use a term ordering and recursion.

(defclass monomial ()
  ((exponents :accessor exponents :initarg :exponents)))

(defclass polynomial ()
  ((terms :accessor terms :initarg :terms)))

(defun make-term (coefficient monomial)
  (cons coefficient monomial))

Finally

(defun make-polynomial-ring (field number-of-variables term-ordering)
  (make-instance 'polynomial-ring
    :coefficients-in field
    :term-ordering term-ordering
    :addition       #'(lambda (x y) (add-polynomials field term-ordering
x y))
    :subtraction    #'(lambda (x y) (subtract-polynomials field
term-ordering x y))
    :negation       #'(lambda (x) (negate-polynomial field x))
    :multiplication #'(lambda (x y) (multiply-polynomials field
term-ordering x y))
    :zero-element (make-null-polynomial)
    :unity-element (make-unity-polynomial field number-of-variables)
    :same-p #'(lambda (x y) (polynomials-same-p field x y))))

This is pretty general.  I didn't optimize it for speed since it was
fast enough for my purposes, namely Groebner basis computation over
arbitrary fields (and rings).

I think the crucial step is to match how the coefficients are stored and
the algorithms you want to use for addition etc.  You can simplify the
implemenation of addition etc if you make sure that the representation
of the coefficients  always satisfies some properties (like being an
ordered list with respect to some term-ordering).  And of course use
funcall to do the computations in your field.

-- 
Clemens Heitzinger
http://ag.or.at:8000/~clemens   (Lisp related material)
From: Michael Hudson
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <m39045qh7d.fsf@atrus.jesus.cam.ac.uk>
Thanks everyone who responded (both in the ng and in email) - about 24
hours after I post I have a dozen or so well considered and helpful
responses. That's cool.

········@ag.or.at (Clemens Heitzinger) writes:

> Michael Hudson <·····@cam.ac.uk> wrote:
> 
> > The project is about polynomials over finite fields. So I need data
> > structures for polynomials and for elements of finite fields.
> > 
> > So I have this:
> > 
> > (defstruct polynomial
> >   coeffs)
> > 
> > (defun add-polynomial (x y) ; is this good style? I don't know!
> >   (let ((a (polynomial-coeffs x))
> >         (b (polynomial-coeffs y)))
> >     (let ((prefix (loop until (or (null a) (null b))
> >                         collect (+ (car a) (car b))
> >                         do (setq a (cdr a))
> >                            (setq b (cdr b)))))
> >       (if (null a) (nconc prefix b) (nconc prefix a))
> >       (make-polynomial :coeffs prefix))))
> 
> Since you store the coefficients in a list, I assume you are only
> interested in univariate polynomial rings K[x], and not e.g. in
> K[x,y,z].

Yup. Though I could regard K[x,y,z] as ((K[X])[Y])[Z], of course.

> I'd do something like
> 
> (defclass field (ring)
>   ((division :accessor division :initarg :division)))

Is ring a standard class? (I'm guessing not) I can see how such a
thing might be built however.

> (defun make-rational-numbers ()
>   (make-instance 'field
>     :name "the rational numbers"
>     :addition #'+ :subtraction #'- :negation #'- :multiplication #'*
> :division #'/
>     :same-p #'eql :zero-element 0 :unity-element 1))

OK... but how do I make a rational? 

(let* ((rat (make-rational-numbers))
       (one (unity-element rat))
       (add (addition rat))
       (div (division rat)))
  (div (add (add one one) one) (add one one)))

to get 3/2 does not appeal... 

Also how do I do things like tell if a given object is a member of
this field?

Actually I suppose you've got functions like:

(defun ring+ (x y) ; is find-class appropriate?
  (funcall (addition (find-class x)) x y))

Sorry, I'm just thinking aloud here....

> and similarly for finite fields.
> 
> > Q2: I'm testing this data structure using integer coefficients but
> > ultimately I'm going to want to use finite field elements. So is it
> > safe to add the coefficients using #'+?
> 
> Of course this depends on the coefficient field.  I think the best way
> is to that start with (rings or) fields (like above) and build the
> polynomial ring from there.  You can choose the make the polynomials
> remember over which field they are defined (ie, they have a slot which
> contains that field), or you can go with something like
> 
> (defun add-polynomials (module term-ordering p1 p2)
>    ...)

I think the former is preferable; is it possible to make specific
fields or rings above both class objects and instances? So you have

rational: instance of field

*and*

q: instance of rational

or, given that I'm new at this, should I avoid such considerations to
try and keep my brain inside my skull? (sorry, Python in-joke)

> > Am I right in thinking that defstruct has nothing to do with CLOS? If
> Yes.

Good. I'm kind of thinking that trying to do what I want with
structures may make me realize the value of the features of CLOS when
I come to them. But life may be too short.
 
> > so is there a more elegeant CLOS-y solution to my problems?
> 
> Well, I have an implementation which starts with monomials and terms and
> stores the coefficient as a list of terms (see outline below).  Addition
> etc of polynomials use a term ordering and recursion.
> 
> (defclass monomial ()
>   ((exponents :accessor exponents :initarg :exponents)))
> 
> (defclass polynomial ()
>   ((terms :accessor terms :initarg :terms)))
> 
> (defun make-term (coefficient monomial)
>   (cons coefficient monomial))

This seems unnecessary for me (with univariate polynomials).

> 
> Finally
> 
> (defun make-polynomial-ring (field number-of-variables term-ordering)
>   (make-instance 'polynomial-ring
>     :coefficients-in field
>     :term-ordering term-ordering
>     :addition       #'(lambda (x y) (add-polynomials field term-ordering
> x y))
>     :subtraction    #'(lambda (x y) (subtract-polynomials field
> term-ordering x y))
>     :negation       #'(lambda (x) (negate-polynomial field x))
>     :multiplication #'(lambda (x y) (multiply-polynomials field
> term-ordering x y))
>     :zero-element (make-null-polynomial)
>     :unity-element (make-unity-polynomial field number-of-variables)
>     :same-p #'(lambda (x y) (polynomials-same-p field x y))))
> 
> This is pretty general.  I didn't optimize it for speed since it was
> fast enough for my purposes, namely Groebner basis computation over
> arbitrary fields (and rings).

Neat. Speed isn't really a concern; good complexity behaviour is
probably a plus.

> I think the crucial step is to match how the coefficients are stored and
> the algorithms you want to use for addition etc.  You can simplify the
> implemenation of addition etc if you make sure that the representation
> of the coefficients  always satisfies some properties (like being an
> ordered list with respect to some term-ordering).  And of course use
> funcall to do the computations in your field.

All good words. Thanks very much (and to all others who responded)
... I'll just scurry off and read the HyperSpec for a bit now.

Regards,
Michael
From: Clemens Heitzinger
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <1e14f0a.1949ijxmjpz4N%cheitzin@ag.or.at>
Michael Hudson <·····@cam.ac.uk> wrote:

> ········@ag.or.at (Clemens Heitzinger) writes:
> > Since you store the coefficients in a list, I assume you are only
> > interested in univariate polynomial rings K[x], and not e.g. in
> > K[x,y,z].
> 
> Yup. Though I could regard K[x,y,z] as ((K[X])[Y])[Z], of course.

The multivariate implementation is probably more practical.  You can
have monomials (their exponents are stored as lists of integers).  Then
printing, input and term-orderings are much easier, and I don't think
this approach has any drawbacks.

> > I'd do something like
> > 
> > (defclass field (ring)
> >   ((division :accessor division :initarg :division)))
> 
> Is ring a standard class? (I'm guessing not) I can see how such a
> thing might be built however.

No; RING has slots for the operations, and a NAME slot.

> > (defun make-rational-numbers ()
> >   (make-instance 'field
> >     :name "the rational numbers"
> >     :addition #'+ :subtraction #'- :negation #'- :multiplication #'*
> > :division #'/
> >     :same-p #'eql :zero-element 0 :unity-element 1))
> 
> OK... but how do I make a rational? 
> 
> (let* ((rat (make-rational-numbers))
>        (one (unity-element rat))
>        (add (addition rat))
>        (div (division rat)))
>   (div (add (add one one) one) (add one one)))
> 
> to get 3/2 does not appeal... 

This is the hard core approach.  I'd simply say 3/2.  ;-)

When you work over GF(p) or Q, I'd just use the CL numbers and use the
right operations, like eg (lambda (x y) (mod (+ x y) p)).

Note that the above would work in Scheme, in CL you would say (funcall
(addition rat) one one).

> Also how do I do things like tell if a given object is a member of
> this field?

Good question.  Add a slot MEMBER-P which holds a function which decides
if the argument is an element or not.

> Actually I suppose you've got functions like:
> 
> (defun ring+ (x y) ; is find-class appropriate?
>   (funcall (addition (find-class x)) x y))
> 
> Sorry, I'm just thinking aloud here....

I didn't actually define functions like that, but there are some
FUNCALLs, but not as many as I initially thought there would be.

[...]
> I think the former is preferable; is it possible to make specific
> fields or rings above both class objects and instances? So you have
> 
> rational: instance of field
> 
> *and*
> 
> q: instance of rational
> 
> or, given that I'm new at this, should I avoid such considerations to
> try and keep my brain inside my skull? (sorry, Python in-joke)

For example, GF(p) would be

(make-instance 'field
  :addition (lambda (x y) (mod (+ x y) p))
  ...)

(You might want to store division using access to a precomputed vector
of the inverses.)

I wouldn't make the elements be instances of a specific class.  This
would decrease the performance drastically, would complicate input and
output, etc, and wouldn't buy you anything in terms of abstraction.  A
MEMBER-P slot is sufficient imo.

> All good words. Thanks very much (and to all others who responded)
> ... I'll just scurry off and read the HyperSpec for a bit now.

You just asked the right news group.  ;-)

-- 
Clemens Heitzinger
http://ag.or.at:8000/~clemens   (Lisp related material)
From: Rainer Joswig
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <joswig-1111991347040001@mac-rjo.work.maz.net>
In article <·······························@ag.or.at>, ········@ag.or.at (Clemens Heitzinger) wrote:

> Michael Hudson <·····@cam.ac.uk> wrote:
> 
> > The project is about polynomials over finite fields. So I need data
> > structures for polynomials and for elements of finite fields.

Did he look at "Weyl"?

From the Documentation:

  Weyl is an extensible algebraic manipulation
  substrate that has been designed to represent all
  types of algebraic objects. It deals not only with the
  basic symbolic objects like polynomials, algebraic
  functions and differential forms, but can also deal
  with higher level objects like groups, rings, ideals
  and vector spaces. Furthermore, to encourage the use
  of symbolic techniques within other applications,
  Weyl is implemented as an extension of Common Lisp
  [8] using the Common Lisp Object Standard [1] so that
  all of Common Lisp's facilities and development tools
  can be used in concert with Weyl's symbolic tools.
  
  
  It should be noted that the initial implementation of
  Weyl is intended to be as clean and semantically
  correct as possible. The primary goal of Weyl is
  provide the tools needed to express algebraic
  algorithms naturally and succinctly. Nonetheless, we
  believe that algebraic algorithms can be effciently
  implemented within the Weyl framework even though
  that was not a goal of the initial implementation.

Rainer Joswig, ISION Internet AG, Harburger Schlossstra�e 1, 
21079 Hamburg, Germany, Tel: +49 40 77175 226
Email: ·············@ision.de , WWW: http://www.ision.de/
From: Michael Hudson
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <m3zowlp0m6.fsf@atrus.jesus.cam.ac.uk>
······@lavielle.com (Rainer Joswig) writes:

> In article <·······························@ag.or.at>, ········@ag.or.at (Clemens Heitzinger) wrote:
> 
> > Michael Hudson <·····@cam.ac.uk> wrote:
> > 
> > > The project is about polynomials over finite fields. So I need data
> > > structures for polynomials and for elements of finite fields.
> 
> Did he look at "Weyl"?

No. But he point of my post was not to get people to solve my problem;
it was improve my understanding of lisp to the point where I can do it
myself. Indeed the project specification says:

   If you use a computer algebra package, then you may find that some
   of the routines asked for in this project are included in the
   package.  In such cases no credit will be given for using the
   packaged routines - you are expected to write your own programs.
   You may wish to compare the answers given by you program and by the
   packaged routines.

so I probably will have a look at it, at least.

Thanks for the pointer.

Regards,
Michael
From: Marco Antoniotti
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <lw1z9xrvwu.fsf@parades.rm.cnr.it>
Is there a site for Weyl?

-- 
Marco Antoniotti ===========================================
PARADES, Via San Pantaleo 66, I-00186 Rome, ITALY
tel. +39 - 06 68 10 03 17, fax. +39 - 06 68 80 79 26
http://www.parades.rm.cnr.it/~marcoxa
From: Hannu Koivisto
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <87d7tht9q2.fsf@senstation.vvf.fi>
Marco Antoniotti <·······@parades.rm.cnr.it> writes:

| Is there a site for Weyl?

<URL:http://www.cs.cornell.edu/Info/Projects/SimLab/>

-- 
Hannu
From: Michael Hudson
Subject: Re: Questions of genericity from a newcomer
Date: 
Message-ID: <m3wvrpp1se.fsf@atrus.jesus.cam.ac.uk>
Marco Antoniotti <·······@parades.rm.cnr.it> writes:

> Is there a site for Weyl?

I found one here:

http://www.cs.cornell.edu/Info/Projects/SimLab/releases/release-1-0.html

Looks pretty cool to this inexperienced undergrad...

Impressively short, too - just 800k of source.

Regards,
Michael