Correct typo in Texinfo: cdf_tributions --> distributions
[maxima/cygwin.git] / src / todd-coxeter.lisp
blob8b52da02b82d861de14d8b17594348244893ec48
1 (in-package :maxima)
3 (defstruct tc-state
4 (nvars 0 :type integer)
5 (ncosets 0 :type integer)
6 (multiply-table nil)
7 (relations nil)
8 (subgroup-generators nil)
9 (row1-relations nil))
11 (defvar $todd_coxeter_state)
13 ;; To turn on debug printing set to T
14 (defvar *debug* nil)
16 ;; When *debug* is not nil, this holds the multiplications for
17 ;; the current row.
18 (defvar *this-row* nil)
20 (deftype coset nil 'integer)
22 ;; The data type we use to enumerate cosets.
24 (defvar *todo* (make-array 10 :element-type 'coset :fill-pointer 0 :adjustable t :initial-element 0))
26 (defmacro with-multiply-table (&body body)
27 `(let ((nvars (tc-state-nvars $todd_coxeter_state))
28 (multiply-table (tc-state-multiply-table $todd_coxeter_state)))
29 (declare (type (vector t) multiply-table))
30 ,@body))
32 (defmacro undef (s)
33 `(eql 0 ,s))
35 ;; Multiply coset K times variable R
36 (defmacro tc-mult (k r)
37 `(the coset (aref (table ,r) ,k)))
39 ;; Force k . r = s and k = s . r^-1
40 (defmacro define-tc-mult (k r s)
41 `(progn
42 (setf (tc-mult ,k ,r) ,s)
43 (setf (tc-mult ,s (- ,r)) ,k)))
45 ;; cosets M < N are to be made equal
46 (defmacro push-todo (m n)
47 `(progn
48 (vector-push-extend ,m *todo*)
49 (vector-push-extend ,n *todo*)))
51 ;; The multiplication table for variable i
52 ;; (can only be used inside with-multiply-table)
53 (defmacro table (i)
54 `(the (vector (coset)) (aref multiply-table (+ ,i nvars))))
57 ;; NVARS is the number of of variables. It should be the maximum
58 ;; of the absolute values of the entries in the relations RELS.
59 ;; The format of the relations is variables X,Y,.. correspond to
60 ;; numbers 1,2,.. and X^^-1, Y^^-1 .. are -1,-2,... RELS is
61 ;; a list of lists in these variables.
62 ;; Thus rels = '((1 -2 -1) (2 2 3) ..) (ie [x1.x2^^-1 . x1^^-1, x2.x2.x3,.. ))
63 ;; SUBGP is also a list of lists.
64 ;; Returns order of G/H, where G is Free/(rels), and H is
65 ;; This is the main entry point at lisp level.
66 ;; Example: (TODD-COXETER 2 '((1 1) (1 2 1 2 1 2) (2 2)))
67 ;; returns 6. In (tc-state-multiply-table $todd_coxeter_state) we find the current
68 ;; state of the action of the variables on the cosets G/H.
69 ;; For computing the symmetric group using the relations
70 ;; p(i,j) :=concat(x,i).concat(x,j);
71 ;; symet(n):=create_list(if (j - i) = 1 then (p(i,j))^^3 else
72 ;; if (not i = j) then (p(i,j))^^2 else p(i,i) , j,1,n-1,i,1,j);
73 ;; todd_coxeter(symet(n)) == n!
74 ;; the running time of the first version of this code is observed to be quadratic
75 ;; in the number of cosets. On a rios it is approx 5*10^-5 * (ncosets)^2.
77 (defun todd-coxeter (nvars rels subgp &aux (i 1) (c 0))
78 (set-up nvars rels subgp)
79 (loop while (>= (tc-state-ncosets $todd_coxeter_state) i)
80 do (incf c) ;; count how many row tries..
81 (cond ((doing-row i) ;; row still being done
82 (replace-coset-in-multiply-table))
83 ((> (fill-pointer *todo*) 0) ;; row finished but there is work to do
84 (incf i)
85 (replace-coset-in-multiply-table))
86 (t ;; row finished -- no work
87 (incf i))))
88 (format t "~%Rows tried ~d~%" c)
89 (tc-state-ncosets $todd_coxeter_state))
91 ;; Store the data in $todd_coxeter_state, and build multiply-table.
92 (defun set-up (nvars rels subgp)
93 (setf (fill-pointer *todo*) 0)
94 (setf $todd_coxeter_state (make-tc-state :nvars nvars
95 :ncosets 1
96 :relations rels
97 :subgroup-generators subgp
98 :row1-relations (append subgp rels)
99 :multiply-table (make-array (1+ (* 2 nvars)))))
101 (with-multiply-table
102 (loop for rel in (tc-state-row1-relations $todd_coxeter_state) do
103 (loop for v in rel
104 do (unless (<= 1 (abs v) nvars)
105 (error "Vars must be integers with absolute value between 1 and ~d" nvars))))
106 (loop for i from (- nvars) to nvars
107 unless (zerop i)
108 do (setf (table i) (make-array 10 :adjustable t :element-type 'coset :initial-element 0)))))
110 ;; Starts multiplying coset i times the relations. Basic fact is i . rel = i.
111 ;; This gives a condition on the multiplication table. Once we have made it all
112 ;; the way through the relations for a given coset i, and NOT had any
113 ;; incosistency in our current multiplication table, then we go on the the next
114 ;; coset. The coset 1 denotes H. so for generators h of H we we have 1 . h = 1.
115 ;; So when we do row 1, we add to the relations the generators of H.
117 ;; When we do find an inconsistency eg: 7 . y = 1 and 4 . y = 1 or 7 = 1 . y^^-1
118 ;; and 4 . y = 1, then we would know that 4 and 7 represent the same coset, and
119 ;; so we put 4 and 7 in the *todo* vector and return t so that
120 ;; replace-coset-in-multiply-table will identify them. While we are running
121 ;; inside doing-row, the multiply-table is accurate, up to our current state of
122 ;; knowledge. Note that once we find such a nonpermutation action of y, we could
123 ;; not maintain the consistency of (table i) and (table -i). We exit doing-row
124 ;; with value t, to indicate replacements should be done, and that we must
125 ;; return to complete row i. (Actually we return t even in the case we were
126 ;; finished the row and found the duplicate in the last step).
128 (defun doing-row (i &aux (j 0) (k 0) (r 0)(s 0) *this-row* relations)
129 (setf relations (if (eql i 1)
130 (tc-state-row1-relations $todd_coxeter_state)
131 (tc-state-relations $todd_coxeter_state)))
132 (with-multiply-table
133 (loop for rel in relations
134 for v on relations
136 (setq k i)
137 (loop
139 (setq r (car rel))
140 (setq s (tc-mult k r))
141 (cond ((undef s)
142 (cond ((cdr rel)
143 (setq s (next-coset))
144 (define-tc-mult k r s))
145 (t (setq s (tc-mult i (- r)))
146 (cond ((undef s) (define-tc-mult k r i))
147 ((< k s) (push-todo k s)(return-from doing-row (cdr v)))
148 ((> k s) (push-todo s k)(return-from doing-row (cdr v))))
149 (loop-finish)))))
150 (cond ((setq rel (cdr rel))
151 (when *debug*
152 (push s *this-row*)
153 (my-print (reverse *this-row*) i))
154 (setq k s)
155 (incf j))
156 ((< i s)
157 (push-todo i s) (return-from doing-row (cdr v)))
158 ((> i s)
159 (push-todo s i) (return-from doing-row (cdr v)))
160 (t ;rel is exhausted and it matched
161 (loop-finish))))))
162 (when *debug*
163 (dcheck-tables)
164 (my-print (reverse *this-row*) i))
165 nil)
167 ;; FILL-IN-INVERSES not only completes the (table i) for i < 0
168 ;; but at the same time checks that (table i) for i > 0
169 ;; does not have repeats. eg if 5 . y = 3 and 7 . y = 3,
170 ;; then this would show up when we go to build the inverse.
171 ;; if it does we add 5 and 7 to the *todo* vector.
173 (defun fill-in-inverses (&aux (s 0) (sp 0))
174 (with-multiply-table
175 (loop for i from 1 to nvars
176 do (let ((ta1 (table i))
177 (ta2 (table (- i))))
178 (declare (type (vector (coset)) ta1 ta2))
179 (loop for j from 1 to (tc-state-ncosets $todd_coxeter_state) do
180 (setf (aref ta2 j) 0))
181 (loop for j from 1 to (tc-state-ncosets $todd_coxeter_state) do
182 (setf s (aref ta1 j))
183 when (not (eql 0 s))
185 (setf sp (aref ta2 s))
186 (cond ((eql 0 sp) (setf (aref ta2 s) j))
187 (t ;; there's a duplicate!
188 (push-todo sp j)
189 (return-from fill-in-inverses t))))))))
191 ;; set n (vector-pop *todo*) , m (vector-pop *todo*)
192 ;; and replace n by m in multiply-table and in *todo*.
193 ;; The replacement is done carefully so as not to lose ANY
194 ;; information from multiply-table, without recording it in
195 ;; *todo*. It finishes by doing FILL-IN-INVERSES which may
196 ;; in turn cause entries to be added to *todo*.
198 (defun replace-coset-in-multiply-table (&aux (m 0) (n 0) (s 0) (s2 0) )
199 (with-multiply-table
200 (tagbody
201 again
202 (setf n (vector-pop *todo*))
203 (setf m (vector-pop *todo*))
204 (unless (eql m n)
205 (dprint-state)
206 (when *debug* (format t " ~a --> ~a " n m))
208 (loop for i from 1 to nvars
210 (let ((ta (table i)))
211 (declare (type (vector (coset)) ta))
212 (setq s2 (tc-mult n i))
213 (unless (undef s2)
214 (setq s (tc-mult m i))
215 (cond ((undef s) (setf (tc-mult m i) s2))
216 ((< s s2) (push-todo s s2))
217 ((> s s2)(push-todo s2 s))))
218 (loop for j downfrom (1- n) to 1
219 do (setq s (aref ta j))
220 (cond ((> s n) (setf (aref ta j) (1- s)))
221 ((eql s n) (setf (aref ta j) m) )))
222 (loop for j from n below (tc-state-ncosets $todd_coxeter_state)
223 do (setq s (aref ta (1+ j)))
224 (cond ((> s n) (setf (aref ta j) (1- s)))
225 ((eql s n) (setf (aref ta j) m) )
226 (t (setf (aref ta j) s))))))
228 (loop for i downfrom (1- (fill-pointer *todo*)) to 0
229 do (setf s (aref *todo* i))
230 (cond ((> s n) (setf (aref *todo* i) (1- s)))
231 ((eql s n)(setf (aref *todo* i) m))))
232 (decf (tc-state-ncosets $todd_coxeter_state))
233 (dprint-state))
235 (when (> (fill-pointer *todo*) 0)
236 (go again))
237 ;;(format t "~%There are now ~a cosets" (tc-state-ncosets $todd_coxeter_state))
238 ;; check for new duplicates introduced!!
239 (when (fill-in-inverses)
240 (go again)))))
242 ;; Get the next coset number, making sure the multiply-table will
243 ;; have room for it, and is appropriately cleaned up.
244 (defun next-coset ()
245 (let* ((n (1+ (tc-state-ncosets $todd_coxeter_state)))
246 (m 0))
247 (with-multiply-table
248 (let ((ta (table 1)))
249 (unless (> (array-total-size ta) (1+ n))
250 (setf m (+ n (ash n -1)))
251 (loop for i from (- nvars) to nvars
252 when (not (eql i 0))
253 do (setf ta (table i))
254 (setf (table i) (adjust-array ta m))))
255 (loop for i from 1 to nvars
256 do (setf (aref (table i) n) 0)
257 (setf (aref (table (- i)) n) 0))))
258 (setf (tc-state-ncosets $todd_coxeter_state) n)))
262 ;; $todd_coxeter parses maxima args
263 ;; todd_coxeter(rels, subgrp) computes the
264 ;; order of G/H where G = Free(listofvars(rels))/subgp_generated(rels));
265 ;; and H is generated by subgp. Subgp defaults to [].
266 ;; todd_coxeter([x^^3,y.x.y^^-1 . x^^-1],[]) gives 6 the order of the symmetric group
267 ;; on 3 elements.
268 ;; todd_coxeter([a^^8,b^^7,a.b.a.b,(a^^-1 . b)^^3],[a^^2, a^^-1 . b]); gives 448
270 (defmfun $todd_coxeter (rels &optional (subgp '((mlist))))
271 (let ((vars ($sort ($listofvars rels)))
272 (neg 1))
273 (todd-coxeter
274 ($length vars)
275 (mapcar #'(lambda (rel) (coerce-rel neg vars rel)) (cdr rels))
276 (mapcar #'(lambda (rel) (coerce-rel neg vars rel)) (cdr subgp)))))
278 (defun coerce-rel (neg vars rel)
279 (if (atom rel)
280 (list (* neg (position rel vars)))
281 (case (caar rel)
282 (mnctimes (apply #'append (mapcar #'(lambda (rel) (coerce-rel neg vars rel)) (cdr rel))))
283 (mncexpt (let* ((n (meval* (third rel)))
284 (neg (signum n))
285 (v (coerce-rel neg vars (second rel))))
286 (loop for i below (abs (third rel))
287 append v)))
288 (otherwise (error "bad rel")))))
290 ;; The following functions are for debugging purposes, and
291 ;; for displaying the rows as they are computed.
293 (defvar *names* '(nil x y z))
295 (defun my-print (ro i &aux relations)
296 (when *debug*
297 (fresh-line)
298 (format t "Row ~a " i)
299 (setq relations (if (eql i 1)
300 (tc-state-row1-relations $todd_coxeter_state)
301 (tc-state-relations $todd_coxeter_state)))
302 (loop for rel in relations do
303 (loop for v on rel do
304 (format t (if (> (car v) 0) "~a" "~(~a~)")
305 (nth (abs (car v)) *names*))
306 (when (null ro) (return-from my-print))
307 (if (cdr v)
308 (princ (pop ro))
309 (format t "~a | ~a" i i))))))
311 (defun has-repeat (ar &aux (j (1+ (tc-state-ncosets $todd_coxeter_state))) ans tem)
312 (loop for k from 1 to (tc-state-ncosets $todd_coxeter_state) do
313 (setq tem (aref ar k))
314 (when (and (not (eql tem 0))
315 (find tem ar :start (1+ k) :end j))
316 (pushnew tem ans)))
317 ans)
319 (defun dcheck-tables (&aux tem)
320 (when *debug*
321 (with-multiply-table
322 (loop for i from 1 to nvars
323 do (if (setq tem (has-repeat (table i)))
324 (format t "~%Table ~a has repeat ~a " i tem))))))
326 (defun dprint-state ()
327 (when *debug*
328 (with-multiply-table
329 (format t "~%Ncosets = ~a, *todo* = ~a" (tc-state-ncosets $todd_coxeter_state) *todo*)
330 (loop for i from 1 to nvars do
331 (format t "~%~a:~a" (nth i *names*) (subseq (table i) 1 (1+ (tc-state-ncosets $todd_coxeter_state)))))
332 (my-print (reverse *this-row*) 0))))