Annotation of OpenXM_contrib/PHC/Ada/Math_Lib/Polynomials/ts_poly.adb, Revision 1.1.1.1
1.1 maekawa 1: with text_io,integer_io; use text_io,integer_io;
2: with Symbol_Table;
3: with Standard_Floating_Numbers; use Standard_Floating_Numbers;
4: with Standard_Complex_Numbers; use Standard_Complex_Numbers;
5: with Standard_Complex_Numbers_io; use Standard_Complex_Numbers_io;
6: with Standard_Complex_Vectors; use Standard_Complex_Vectors;
7: with Standard_Complex_Vectors_io; use Standard_Complex_Vectors_io;
8: with Standard_Random_Vectors; use Standard_Random_Vectors;
9: with Standard_Complex_Polynomials; use Standard_Complex_Polynomials;
10: with Standard_Complex_Polynomials_io; use Standard_Complex_Polynomials_io;
11: with Standard_Complex_Poly_Vectors; use Standard_Complex_Poly_Vectors;
12: with Standard_Complex_Poly_Vectors_io; use Standard_Complex_Poly_Vectors_io;
13: with Standard_Complex_Poly_Matrices; use Standard_Complex_Poly_Matrices;
14: with Standard_Complex_Poly_Matrices_io; use Standard_Complex_Poly_Matrices_io;
15: with Standard_Complex_Poly_Functions; use Standard_Complex_Poly_Functions;
16: with Standard_Complex_Poly_Systems; use Standard_Complex_Poly_Systems;
17: with Standard_Complex_Poly_Systems_io; use Standard_Complex_Poly_Systems_io;
18: with Standard_Complex_Poly_SysFun; use Standard_Complex_Poly_SysFun;
19: with Standard_Complex_Laur_Polys; use Standard_Complex_Laur_Polys;
20: with Standard_Complex_Laur_Functions; use Standard_Complex_Laur_Functions;
21: with Standard_Poly_Laur_Convertors; use Standard_Poly_Laur_Convertors;
22: with Standard_to_Multprec_Convertors; use Standard_to_Multprec_Convertors;
23: with Multprec_Complex_Numbers; use Multprec_Complex_Numbers;
24: with Multprec_Complex_Numbers_io; use Multprec_Complex_Numbers_io;
25: with Multprec_Complex_Vectors; use Multprec_Complex_Vectors;
26: with Multprec_Complex_Vectors_io; use Multprec_Complex_Vectors_io;
27: with Multprec_Complex_Vector_Tools; use Multprec_Complex_Vector_Tools;
28: with Multprec_Complex_Polynomials; use Multprec_Complex_Polynomials;
29: with Multprec_Complex_Polynomials_io; use Multprec_Complex_Polynomials_io;
30: with Multprec_Complex_Poly_Functions; use Multprec_Complex_Poly_Functions;
31: with Multprec_Complex_Poly_Systems; use Multprec_Complex_Poly_Systems;
32: with Multprec_Complex_Poly_SysFun; use Multprec_Complex_Poly_SysFun;
33:
34: procedure ts_poly is
35:
36: -- DESCRIPTION :
37: -- This routine provides basic testing routines for complex polynomials.
38:
39: procedure Test_io is
40:
41: -- DESCRIPTION :
42: -- Tests the input/output of a polynomial in several variables
43: -- and with complex coefficients.
44:
45: n,m : natural;
46: p : Standard_Complex_Polynomials.Poly;
47:
48: begin
49: new_line;
50: put_line("Interactive testing of input/output of complex polynomials.");
51: new_line;
52: put("Give the number of variables : "); get(n);
53: Symbol_Table.Init(n);
54: put_line("Give a polynomial (terminate with ;) : "); get(p);
55: m := Number_of_Unknowns(p);
56: put("the number of unknowns : "); put(m,1); new_line;
57: put("the number of terms : "); put(Number_of_Terms(p),1); new_line;
58: put("the degree of p : "); put(Degree(p),1);
59: put(" max degrees : ");
60: for i in 1..m loop
61: put(Degree(p,i),1); put(" ");
62: end loop;
63: new_line;
64: put_line("Your polynomial : "); put(p); new_line;
65: Symbol_Table.Clear;
66: Clear(p);
67: end Test_io;
68:
69: procedure Test_Vector_io is
70:
71: n : natural;
72:
73: begin
74: new_line;
75: put_line("Interactive testing of i/o of vectors of complex polynomials.");
76: new_line;
77: put("Give the dimension of the vector : "); get(n);
78: Symbol_Table.Init(n);
79: declare
80: p : Standard_Complex_Poly_Vectors.Vector(1..n);
81: begin
82: put("Give "); put(n,1); put(" polynomials in "); put(n,1);
83: put_line(" variables : "); get(p);
84: put_line("Your polynomials : "); put_line(p);
85: end;
86: end Test_Vector_io;
87:
88: procedure Test_Matrix_io is
89:
90: n : natural;
91:
92: begin
93: new_line;
94: put_line("Interactive testing of i/o of matrices of complex polynomials.");
95: new_line;
96: put("Give the dimension of the matrix : "); get(n);
97: Symbol_Table.Init(n);
98: declare
99: p : Matrix(1..n,1..n);
100: begin
101: put("Give "); put(n,1); put("x"); put(n,1);
102: put(" polynomial matrix in "); put(n,1);
103: put_line(" variables : "); get(p);
104: put_line("Your polynomial matrix : "); put(p);
105: end;
106: end Test_Matrix_io;
107:
108: procedure Test_Standard_Eval
109: ( p : in Standard_Complex_Polynomials.Poly;
110: e : in Standard_Complex_Poly_Functions.Eval_Poly;
111: x : in Standard_Complex_Vectors.Vector;
112: output_of_results : in boolean; bug : out boolean ) is
113:
114: -- DESCRIPTION :
115: -- Evaluates the polynomial twice and compares the results.
116:
117: y1 : Standard_Complex_Numbers.Complex_Number := Eval(p,x);
118: y2 : Standard_Complex_Numbers.Complex_Number := Eval(e,x);
119: tol : constant double_float := 10.0**(-12);
120:
121: begin
122: if AbsVal(y1-y2) < tol
123: then put_line("Test on evaluation is successful."); bug := false;
124: else put_line("Different results! Bug detected."); bug := true;
125: end if;
126: if output_of_results or bug
127: then put("p(x) : "); put(y1); new_line;
128: put("e(x) : "); put(y2); new_line;
129: end if;
130: end Test_Standard_Eval;
131:
132: procedure Test_Standard_Laurent_Eval
133: ( p : in Standard_Complex_Laur_Polys.Poly;
134: e : in Standard_Complex_Laur_Functions.Eval_Poly;
135: x : in Standard_Complex_Vectors.Vector;
136: output_of_results : in boolean; bug : out boolean ) is
137:
138: -- DESCRIPTION :
139: -- Evaluates the polynomial twice and compares the results.
140:
141: y1 : Standard_Complex_Numbers.Complex_Number := Eval(p,x);
142: y2 : Standard_Complex_Numbers.Complex_Number := Eval(e,x);
143: tol : constant double_float := 10.0**(-12);
144:
145: begin
146: if AbsVal(y1-y2) < tol
147: then put_line("Test on evaluation is successful."); bug := false;
148: else put_line("Different results! Bug detected."); bug := true;
149: end if;
150: if output_of_results or bug
151: then put("p(x) : "); put(y1); new_line;
152: put("e(x) : "); put(y2); new_line;
153: end if;
154: end Test_Standard_Laurent_Eval;
155:
156: procedure Interactive_Standard_Eval is
157:
158: -- DESCRIPTION :
159: -- Tests the evaluation of a polynomial in several variables
160: -- and with standard complex coefficients.
161:
162: n : natural;
163: p : Standard_Complex_Polynomials.Poly;
164: e : Standard_Complex_Poly_Functions.Eval_Poly;
165: bug : boolean;
166: ans : character;
167:
168: begin
169: new_line;
170: put_line("Interactive evaluation of standard complex polynomials.");
171: new_line;
172: put("Give the number of variables : "); get(n);
173: Symbol_Table.Init(n);
174: put_line("Give a polynomial (terminate with ;) : "); get(p);
175: put_line("Your polynomial p : "); put(p); new_line;
176: e := Create(p);
177: loop
178: declare
179: x : Standard_Complex_Vectors.Vector(1..n);
180: begin
181: put("Give "); put(n,1); put_line(" complex numbers : "); get(x);
182: Test_Standard_Eval(p,e,x,true,bug);
183: end;
184: put("Do you wish to evaluate at other points (y/n) ? "); get(ans);
185: exit when (ans /= 'y');
186: end loop;
187: Symbol_Table.Clear;
188: Clear(p); Clear(e);
189: end Interactive_Standard_Eval;
190:
191: procedure Interactive_Standard_Laurent_Eval is
192:
193: -- DESCRIPTION :
194: -- Tests the evaluation of a polynomial in several variables
195: -- and with standard complex coefficients.
196:
197: n : natural;
198: p : Standard_Complex_Polynomials.Poly;
199: lp : Standard_Complex_Laur_Polys.Poly;
200: elp : Standard_Complex_Laur_Functions.Eval_Poly;
201: bug : boolean;
202: ans : character;
203:
204: begin
205: new_line;
206: put_line("Interactive evaluation of standard complex Laurent polynomials.");
207: new_line;
208: put("Give the number of variables : "); get(n);
209: Symbol_Table.Init(n);
210: put_line("Give a polynomial (terminate with ;) : "); get(p);
211: put_line("Your polynomial p : "); put(p); new_line;
212: lp := Polynomial_to_Laurent_Polynomial(p);
213: elp := Create(lp);
214: loop
215: declare
216: x : Standard_Complex_Vectors.Vector(1..n);
217: begin
218: put("Give "); put(n,1); put_line(" complex numbers : "); get(x);
219: Test_Standard_Laurent_Eval(lp,elp,x,true,bug);
220: end;
221: put("Do you wish to evaluate at other points (y/n) ? "); get(ans);
222: exit when (ans /= 'y');
223: end loop;
224: Symbol_Table.Clear;
225: Clear(p); Clear(lp); Clear(elp);
226: end Interactive_Standard_Laurent_Eval;
227:
228: procedure Random_Standard_Eval is
229:
230: -- DESCRIPTION :
231: -- Tests the evaluation of a polynomial in several variables
232: -- and with standard complex coefficients.
233:
234: n,nb : natural;
235: p : Standard_Complex_Polynomials.Poly;
236: e : Standard_Complex_Poly_Functions.Eval_Poly;
237: bug : boolean;
238:
239: begin
240: new_line;
241: put_line("Random evaluation of standard complex polynomials.");
242: new_line;
243: put("Give the number of variables : "); get(n);
244: Symbol_Table.Init(n);
245: put_line("Give a polynomial (terminate with ;) : "); get(p);
246: put_line("Your polynomial p : "); put(p); new_line;
247: e := Create(p);
248: put("Give the number of samples : "); get(nb);
249: for i in 1..nb loop
250: declare
251: x : constant Standard_Complex_Vectors.Vector := Random_Vector(1,n);
252: begin
253: Test_Standard_Eval(p,e,x,false,bug);
254: end;
255: exit when bug;
256: end loop;
257: Symbol_Table.Clear;
258: Clear(p); Clear(e);
259: end Random_Standard_Eval;
260:
261: procedure Random_Standard_Laurent_Eval is
262:
263: -- DESCRIPTION :
264: -- Tests the evaluation of a Laurent polynomial in several variables
265: -- and with standard complex coefficients.
266:
267: n,nb : natural;
268: p : Standard_Complex_Polynomials.Poly;
269: lp : Standard_Complex_Laur_Polys.Poly;
270: elp : Standard_Complex_Laur_Functions.Eval_Poly;
271: bug : boolean;
272:
273: begin
274: new_line;
275: put_line("Random evaluation of standard complex Laurent polynomials.");
276: new_line;
277: put("Give the number of variables : "); get(n);
278: Symbol_Table.Init(n);
279: put_line("Give a polynomial (terminate with ;) : "); get(p);
280: put_line("Your polynomial p : "); put(p); new_line;
281: lp := Polynomial_to_Laurent_Polynomial(p);
282: elp := Create(lp);
283: put("Give the number of samples : "); get(nb);
284: for i in 1..nb loop
285: declare
286: x : constant Standard_Complex_Vectors.Vector := Random_Vector(1,n);
287: begin
288: Test_Standard_Laurent_Eval(lp,elp,x,false,bug);
289: end;
290: exit when bug;
291: end loop;
292: Symbol_Table.Clear;
293: Clear(p); Clear(lp); Clear(elp);
294: end Random_Standard_Laurent_Eval;
295:
296: procedure Test_Multprec_Eval is
297:
298: -- DESCRIPTION :
299: -- Tests the evaluation of a polynomial in several variables
300: -- and with multi-precision complex coefficients.
301:
302: ans : character;
303: n : natural;
304: p : Standard_Complex_Polynomials.Poly;
305: mp : Multprec_Complex_Polynomials.Poly;
306: ep : Multprec_Complex_Poly_Functions.Eval_Poly;
307:
308: begin
309: new_line;
310: put_line("Testing the evaluation of multi-precision complex polynomials.");
311: new_line;
312: put("Give the number of variables : "); get(n);
313: Symbol_Table.Init(n);
314: put_line("Give a polynomial (terminate with ;) : "); get(p);
315: put_line("Your polynomial p : "); put(p); new_line;
316: mp := Convert(p);
317: ep := Create(mp);
318: declare
319: x : Multprec_Complex_Vectors.Vector(1..n);
320: sz : natural;
321: y1,y2 : Multprec_Complex_Numbers.Complex_Number;
322: begin
323: put("Give "); put(n,1); put_line(" complex numbers : "); get(x);
324: loop
325: put("Give the size of the numbers : "); get(sz);
326: Set_Size(x,sz);
327: y1 := Eval(mp,x); put("p(x) : "); put(y1); new_line;
328: y2 := Eval(ep,x); put("e(x) : "); put(y2); new_line;
329: if Equal(y1,y2)
330: then put_line("Test on evaluation is successful.");
331: else put_line("Different results! Bug detected.");
332: end if;
333: put("Do you want to evaluate for other precisions ? (y/n) ");
334: get(ans);
335: exit when ans /= 'y';
336: end loop;
337: end;
338: Symbol_Table.Clear;
339: Clear(p); Clear(mp); Clear(ep);
340: end Test_Multprec_Eval;
341:
342: procedure Test_Standard_Diff is
343:
344: -- DESCRIPTION :
345: -- Test on the differentiation of standard complex polynomials.
346:
347: n,m : natural;
348: p,dp : Standard_Complex_Polynomials.Poly;
349:
350: begin
351: new_line;
352: put_line("Test on differentiation of standard complex polynomials.");
353: new_line;
354: put("Give the number of variables : "); get(n);
355: Symbol_Table.Init(n);
356: put_line("Give a polynomial (terminate with ;) : "); get(p);
357: m := Number_of_Unknowns(p);
358: put("Your polynomial p : "); put(p); new_line;
359: put("The number of unknowns : "); put(m,1); new_line;
360: for i in 1..m loop
361: dp := Diff(p,i);
362: put("Diff(p,"); put(i,1); put(") : ");
363: put(dp); new_line;
364: Clear(dp);
365: end loop;
366: Symbol_Table.Clear;
367: Clear(p);
368: end Test_Standard_Diff;
369:
370: procedure Test_Multprec_Diff is
371:
372: -- DESCRIPTION :
373: -- Test on the differentiation of multi-precision complex polynomials.
374:
375: n,m : natural;
376: p : Standard_Complex_Polynomials.Poly;
377: mp,dp : Multprec_Complex_Polynomials.Poly;
378:
379: begin
380: new_line;
381: put_line("Test on differentiation of multi-precision complex polynomials.");
382: new_line;
383: put("Give the number of variables : "); get(n);
384: Symbol_Table.Init(n);
385: put_line("Give a polynomial (terminate with ;) : "); get(p);
386: m := Number_of_Unknowns(p);
387: put("Your polynomial p : "); put(p); new_line;
388: mp := Convert(p);
389: put("As multi-precision poly : "); put(mp); new_line;
390: put("The number of unknowns : "); put(m,1); new_line;
391: for i in 1..m loop
392: dp := Diff(mp,i);
393: put("Diff(p,"); put(i,1); put(") : ");
394: put(dp); new_line;
395: Clear(dp);
396: end loop;
397: Symbol_Table.Clear;
398: Clear(p); Clear(mp);
399: end Test_Multprec_Diff;
400:
401: procedure Test_System_io is
402:
403: lp : Standard_Complex_Poly_Systems.Link_to_Poly_Sys;
404: n : natural;
405:
406: begin
407: new_line;
408: put_line("Interactive testing on input/output of polynomial systems.");
409: new_line;
410: put("Give the dimension : "); get(n);
411: Symbol_Table.Init(n);
412: put("Give "); put(n,1); put_line(" polynomials : ");
413: declare
414: p : Standard_Complex_Poly_Systems.Poly_Sys(1..n);
415: begin
416: get(p);
417: put_line("The system : "); put(p);
418: end;
419: Symbol_Table.Clear;
420: get(lp);
421: put_line("The system : "); put(lp.all);
422: end Test_System_io;
423:
424: procedure Test_Eval_Standard_System is
425:
426: lp : Standard_Complex_Poly_Systems.Link_to_Poly_Sys;
427:
428: begin
429: new_line;
430: put_line("Testing the evaluation of standard polynomial systems.");
431: new_line;
432: get(lp);
433: put_line("The system : "); put(lp.all);
434: declare
435: n : constant natural := lp'last;
436: x,y1,y2,y3 : Standard_Complex_Vectors.Vector(1..n);
437: ep : Standard_Complex_Poly_SysFun.Eval_Poly_Sys(1..n) := Create(lp.all);
438:
439: function Evaluate ( x : Standard_Complex_Vectors.Vector )
440: return Standard_Complex_Vectors.Vector is
441: begin
442: return Eval(ep,x);
443: end Evaluate;
444: begin
445: put("Give "); put(n,1); put_line(" complex numbers :"); get(x);
446: y1 := Eval(lp.all,x);
447: y2 := Eval(ep,x);
448: y3 := Evaluate(x);
449: put("p(x) : "); put(y1); new_line;
450: put("e(x) : "); put(y2); new_line;
451: put("E(x) : "); put(y2); new_line;
452: if Equal(y1,y2) and Equal(y2,y3)
453: then put_line("Test on evaluation of system is successful.");
454: else put_line("Different evaluations! Bug detected.");
455: end if;
456: end;
457: end Test_Eval_Standard_System;
458:
459: procedure Test_Eval_Multprec_System is
460:
461: lp : Standard_Complex_Poly_Systems.Link_to_Poly_Sys;
462:
463: begin
464: new_line;
465: put_line("Testing the evaluation of multi-precision polynomial systems.");
466: new_line;
467: get(lp);
468: put_line("The system : "); put(lp.all);
469: declare
470: n : constant natural := lp'last;
471: x,y1,y2 : Multprec_Complex_Vectors.Vector(1..n);
472: mp : Multprec_Complex_Poly_Systems.Poly_Sys(1..n) := Convert(lp.all);
473: ep : Multprec_Complex_Poly_SysFun.Eval_Poly_Sys(1..n) := Create(mp);
474: begin
475: put("Give "); put(n,1); put_line(" complex numbers :"); get(x);
476: y1 := Eval(mp,x);
477: y2 := Eval(ep,x);
478: put("p(x) : "); put(y1); new_line;
479: put("e(x) : "); put(y2); new_line;
480: if Equal(y1,y2)
481: then put_line("Test on evaluation of system is successful.");
482: else put_line("Different evaluations! Bug detected.");
483: end if;
484: end;
485: end Test_Eval_Multprec_System;
486:
487: procedure Main is
488:
489: ans : character;
490:
491: begin
492: new_line;
493: put_line("Interactive testing of the operations on complex polynomials.");
494: loop
495: new_line;
496: put_line("Choose one of the following : ");
497: put_line(" 0. Exit this program. ");
498: put_line(" 1. i/o of standard complex polynomials. ");
499: put_line(" 2. i/o of vectors of standard complex polynomials. ");
500: put_line(" 3. i/o of matrices of standard complex polynomials. ");
501: put_line(" 4. Interactive evaluation of standard complex polynomials.");
502: put_line(" 5. Interactive evaluation of standard Laurent polynomials.");
503: put_line(" 6. Random evaluation of standard complex polynomials. ");
504: put_line(" 7. Random evaluation of standard Laurent polynomials. ");
505: put_line(" 8. Evaluation of multi-precision complex polynomials. ");
506: put_line(" 9. Differentiation of standard complex polynomials. ");
507: put_line(" A. Differentiation of multi-precision complex polynomials.");
508: put_line(" B. i/o of systems of standard complex polynomials. ");
509: put_line(" C. Evaluation of systems of standard complex polynomials. ");
510: put_line(" D. Evaluation of systems of multprec complex polynomials. ");
511: put("Type 0,1,2,3,4,5,6,7,8,9,A,B,C or D to select : "); get(ans);
512: exit when (ans = '0');
513: case ans is
514: when '1' => Test_io;
515: when '2' => Test_Vector_io;
516: when '3' => Test_Matrix_io;
517: when '4' => Interactive_Standard_Eval;
518: when '5' => Interactive_Standard_Laurent_Eval;
519: when '6' => Random_Standard_Eval;
520: when '7' => Random_Standard_Laurent_Eval;
521: when '8' => Test_Multprec_Eval;
522: when '9' => Test_Standard_Diff;
523: when 'A' => Test_Multprec_Diff;
524: when 'B' => Test_System_io;
525: when 'C' => Test_Eval_Standard_System;
526: when 'D' => Test_Eval_Multprec_System;
527: when others => null;
528: end case;
529: end loop;
530: end Main;
531:
532: begin
533: Main;
534: end ts_poly;
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>