Annotation of OpenXM/src/k097/help.k, Revision 1.7
1.7 ! takayama 1: /* $OpenXM: OpenXM/src/k097/help.k,v 1.6 2000/12/29 07:19:39 takayama Exp $ */
1.1 maekawa 2: if (K00_verbose)
3: Println("help.k (help.ccc). 8/6, 1996 --- 8/7, 1996. 3/6, 1997 --- 12/21, 1997.");
4:
5: def help(x) {
6: if (Length(Arglist) < 1) {
7: ShowKeyWords(" ");
8: } else {
9: Help(x);
10: }
11: }
12:
13:
14: def Help(key) {
15: local n,i,item,m,item1,j;
16: if (Length(Arglist) < 1) {
17: ShowKeyWords(" ");
18: return( [ ] );
19: }
20:
21: if (key == "ALL") {
22: ShowKeyWords("ALL"); return(0);
23: }
24: n = Length(Helplist);
25: PSfor (i=0; i<n; i++) {
26: item = Helplist[i];
27: if (item[0] == key) {
28: if (IsArray(item[1])) {
29: item1 = item[1];
30: m = Length(item1);
31: for (j=0; j<m; j++) {
32: Println(item1[j]);
33: }
34: }else{
35: Println(item[1]);
36: }
37: return(item);
38: }
39: }
40: Print("The key word <<"); Print(key); Println(">> could not be found.");
41: return([ ]);
42: }
43:
44:
45: def ShowKeyWords(ss) {
46: local i,j,n,keys,max,width,m,k,kk,tmp0;
47: Ln();
48: n = Length(Helplist);
49: keys = [" " ]; /* This is a gate keeper for shell. */
50: PSfor (i=0; i< n; i++ ) {
51: keys = Append(keys,Helplist[i,0]);
52: }
53: keys = sm1(keys," shell ");
54: n = Length(keys);
55: if (ss == "ALL") {
56: PSfor (i=1; i<n; i++) {
57: Print("# "); Print(keys[i]); Ln();
58: Help(keys[i]); Ln();
59: }
60: return(0);
61: }
62: max = 0;
63: PSfor (i=1; i<n; i++) {
64: if (Length(keys[i]) > max) {
65: max = Length(keys[i]);
66: }
67: }
68: /* Println(max); */
69: max = max+3;
70: width = 80;
71: m = 0;
72: while ((m*max) < 80) {
73: m = m+1;
74: }
75: if (m > 1) m = m-1;
76: k = 0; kk = 0;
77: PSfor (i=1; i<n; i++) {
78: Print(keys[i]); kk = kk+1;
79: k = k+Length(keys[i]);
80: tmp0 = max-Length(keys[i]);
81: /*for (j=0; j < tmp0 ; j++) {
82: k = k+1;
83: if (kk < m) {Print(" ");}
84: }*/
85: k = k+tmp0;
86: if (kk < m) {
87: sm1(" [ 0 1 ", tmp0, " (integer) dc 1 sub { pop $ $ } for ] aload length cat_n messagen ");
88: }
89: if (kk >= m) {
90: kk = 0; k=0; Ln();
91: }
92: }
93: Ln();
94: Println("Type in Help(keyword); to see a help message (string keyword).");
95:
96: /* Println(keys); */
97: }
98:
99: def ShowKeyWordsOfSm1(ss) {
100: local i,j,n,keys,max,width,m,k,kk,tmp0;
101: Ln();
102: sm1(" /help_Sm1Macro @.usages def ");
103: n = Length(help_Sm1Macro);
104: keys = [" " ];
105: for (i=0; i< n; i++ ) {
106: keys = Append(keys,help_Sm1Macro[i,0]);
107: }
108: keys = sm1(keys," shell ");
109: n = Length(keys);
110: if (ss == "ALL") {
111: for (i=1; i<n; i++) {
112: tmp0 = keys[i];
113: Print("# "); Print(tmp0); Ln();
114: sm1(tmp0," usage "); Ln();
115: }
116: return(0);
117: }
118:
119: max = 0;
120: for (i=1; i<n; i++) {
121: if (Length(keys[i]) > max) {
122: max = Length(keys[i]);
123: }
124: }
125: /* Println(max); */
126: max = max+3;
127: width = 80;
128: m = 0;
129: while ((m*max) < 80) {
130: m = m+1;
131: }
132: k = 0; kk = 0;
133: for (i=1; i<n; i++) {
134: Print(keys[i]); kk = kk+1;
135: k = k+Length(keys[i]);
136: tmp0 = max-Length(keys[i]);
137: if (kk >= m) {
138: }else {
139: for (j=0; j < tmp0 ; j++) {
140: k = k+1;
141: Print(" ");
142: }
143: }
144: if (kk >= m) {
145: kk = 0; k=0; Ln();
146: }
147: }
148: Ln();
149: Ln();
150: Println("Type in (keyword) usage ; to see a help message.");
151:
152: /* Println(keys); */
153: }
154:
155: HelpAdd(["Help", "Help(key) shows an explanation on the key (string key)."]);
156: HelpAdd(["HelpAdd",
157: ["HelpAdd([key,explanation]) (string key, string explanation)",
158: " or (string key, array explanation)."]]);
159: HelpAdd(["load",
160: ["load(fname) loads the file << fname >>(string fname).",
161: "load fname loads the file << fname >>.",
162: "load[fname] loads the file << fname >> with the preprocessing by /lib/cpp."
163: ]]);
164: HelpAdd(["Ln","Ln() newline."]);
165: HelpAdd(["Println","Println(f) prints f and goes to the new line."]);
166: HelpAdd(["Print","Print(f) prints f."]);
167: HelpAdd(["Poly",
168: "Poly(name) returns the polynomial name in the current ring
169: (string name)."]);
170: HelpAdd(["PolyR",
1.7 ! takayama 171: ["PolyR(name,r) returns the polynomial name in the ring r
! 172: (string name, ring r).",
! 173: "Ex. r = RingD(\"x,y\"); y = PolyR(\"y\",r); "]]);
1.1 maekawa 174: HelpAdd(["RingD",
175: ["RingD(names) defines a new ring (string names).",
176: "RingD(names,weight_vector) defines a new ring with the weight vector",
177: "(string names, array weight_vector).",
178: "RingD(names,weight_vector,characteristic)",
179: " Ex. RingD(\"x,y\",[[\"x\",2,\"y\",1]]) "]]);
180: HelpAdd(["Reduction","Reduction(f,G) returns the remainder and sygygies when
181: f is devided by G (polynomial f, array G)."]);
182: HelpAdd(["AddString","AddString(list) returns the concatnated string (array list)."]);
183: HelpAdd(["AsciiToString","AsciiToString(ascii_code) returns the string of which
184: ascii code is ascii_code (integer ascii_code)."]);
185: HelpAdd(["ToString","ToString(obj) transforms the <<obj>> to a string."]);
186: HelpAdd(["Numerator","Numerator(f) returns the numerator of <<f>> (rational f)."]);
187: HelpAdd(["Denominator","Denominator(f) returns the denominator of <<f>> (rational f)."]);
1.7 ! takayama 188: HelpAdd(["Replace",
! 189: ["Replace(f,rule) (polynomial f, array rule). ",
! 190: "Ex. Replace( (x+y)^3, [[x,Poly(\"1\")]])"]]);
1.1 maekawa 191: HelpAdd(["SetRingVariables",
192: "SetRingVariables()
193: Set the generators of the current ring as global variables.
194: cf. RingD(), Poly(), PolyR()"]);
195: HelpAdd(["Append","Append([f1,...,fn],g) returns the list [f1,...,fn,g]"]);
196: HelpAdd(["Join",
197: "Join([f1,...,fn],[g1,...,gm]) returns the list
198: [f1,...,fn,g1,...,gm]"]);
199: HelpAdd(["Indexed",
200: "Indexed(name,i) returns the string name[i]
201: (string name, integer i)"]);
202:
203: HelpAdd(["-ReservedName1",
204: ["The names k00*, K00*, sm1* , arg1,arg2,arg3,arg4,....," ,
205: "Helplist, Arglist, FunctionValue,",
206: "@@@*, db.*, k.*, tmp002*, tmp00* are used for system functions."]]);
207:
208: HelpAdd(["IntegerToSm1Integer",
209: "IntegerToSm1Integer(i) translates integer i
210: to sm1.integer (integer i)."]);
211: HelpAdd(["true","true returns sm1.integer 1."]);
212: HelpAdd(["false","false returns sm1.integer 0."]);
213: HelpAdd(["IsArray",
214: ["If f is the array object, then IsArray(f) returns true,",
215: "else IsArray(f) returns false."]]);
216:
217:
218:
219: HelpAdd(["Init_w",
220: ["Init_w(f,vars,w) returns the initial terms with respect to the",
221: "weight vector <<w>> (array of integer) of the polynomial <<f>>",
222: "(polynomial). Here, <<f>> is regarded as a polynomial with respect",
223: "to the variables <<vars>> (array of polynomials).",
224: "Example: Init_w(x^2+y^2+x,[x,y],[1,1]):"]]);
225:
226: HelpAdd(["RingDonIndexedVariables",
227: ["RingDonIndexedVariables(name,n) defines and returns the ring of",
228: "homogenized differential operators",
229: "Q<h, name[0], ..., name[n-1], Dname[0], ..., Dname[n-1]>",
230: "where <<name>> is a string and <<n>> is an integer.",
231: "Note that this function defines global variables",
232: "h, name[0], ..., name[n-1], Dname[0], ..., Dname[n-1].",
233: "Example: RingDonIndexedVariables(\"x\",3).",
234: "RingDonIndexedVariables(name,n,w) defines and returns the ring of",
235: "homogenized differential operators with the ordering defined by ",
236: "the weight vector <<w>> (array)",
237: "Example: RingDonIndexedVariables(\"x\",3,[[\"x[0]\",1,\"x[2]\",3]])."]]);
238:
239: HelpAdd(["Groebner",
240: ["Groebner(input) returns Groebner basis of the left module (or ideal)",
241: "defined by <<input>> (array of polynomials)",
242: "The order is that of the ring to which each element of <<input>>",
243: "belongs.",
244: "The input is automatically homogenized.",
245: "Example: RingD(\"x,y\",[[\"x\", 10, \"y\", 1]]);",
246: " Groebner([Poly(\" x^2+y^2-4\"),Poly(\" x*y-1 \")]):",
247: "cf. RingD, Homogenize"]]);
248:
249:
250: HelpAdd(["RingPoly",
251: ["RingPoly(names) defines a Ring of Polyomials (string names).",
252: "The names of variables of that ring are <<names>> and ",
253: "the homogenization variable h.",
254: "cf. SetRingVariables, RingD",
255: "Example: R=RingPoly(\"x,y\");",
256: " ",
257: "RingPoly(names,weight_vector) defines a Ring of Polynomials",
258: "with the order defined by the << weight_vector >>",
259: "(string names, array of array weight_vector).",
260: "RingPoly(names,weight_vector,characteristic)",
261: "Example: R=RingPoly(\"x,y\",[[\"x\",10,\"y\",1]]);",
262: " (x+y)^10: "]]);
263:
264:
265: HelpAdd(["CancelNumber",
266: ["CancelNumber(rn) reduces the rational number <<rn>>",
267: "(rational rn).",
268: "Example: CancelNumber( 2/6 ) : "]]);
269:
270: HelpAdd(["IsString",
271: ["IsString(obj) returns true if << obj >> is a string (object obj).",
272: "Example: if (IsString(\"abc\")) Println(\"Hello\"); ;"]]);
273:
1.6 takayama 274: HelpAdd(["IsRing",
275: ["IsRing(obj) returns true if << obj >> is a ring (object obj)."
276: ]]);
277:
1.1 maekawa 278:
279: HelpAdd(["IsSm1Integer",
280: ["IsSm1Integer(obj) returns true if << obj >> is an integer of sm1(object obj)."]]);
281:
282: HelpAdd(["sm1",
283: ["sm1(arg1,arg2,...) is used to embed sm1 native code in the kxx program.",
284: "Example: sm1( 2, 2, \" add print \"); ",
285: "Example: def myadd(a,b) { sm1(a,b,\" add /FunctionValue set \"); }" ]]);
286:
287: HelpAdd(["DC",
288: ["DC(obj,key) converts << obj >> to a new object in the primitive",
289: "class << key >> (object obj, string key)",
290: "Example: DC(\" (x+1)^10 \", \"polynomial\"): "]]);
291:
292: HelpAdd(["Length",
293: ["Length(vec) returns the length of the array << vec >>",
294: "(array vec)"]]);
295:
296: HelpAdd(["Transpose",
297: ["Transpose(m) return the transpose of the matrix << m >>",
298: "(array of array m)."]]);
299:
300: HelpAdd(["Save",
301: ["Save(obj) appends << obj >> to the file sm1out.txt (object obj)."]]);
302:
303: HelpAdd(["Coefficients",
304: ["Coefficients(f,v) returns [exponents, coefficients] of << f >>",
305: "with respect to the variable << v >>",
306: "(polynomial f,v).",
307: "Example: Coefficients(Poly(\"(x+1)^2\"),Poly(\"x\")): "]]);
308:
309: HelpAdd(["System",
310: ["System(comm) executes the unix system command << comm >>",
311: "(string comm)",
312: "Example: System(\"ls\");"]]);
313:
314: HelpAdd(["Exponent",
315: ["Expoent(f,vars) returns the vector of exponents of the polynomial f",
316: "Ex. Exponent( x^2*y-1,[x,y])"]]);
317:
318: HelpAdd(["Protect",
319: ["Protect(name) protects the symbol <<name>> (string)",
320: "Protect(name,level) protects the symbol <<name>> (string) with ",
321: "<<level>> "]]);
322:
323: HelpAdd(["IsPolynomial",
324: ["IsPolynomial(f) returns true if <<f>> (object) is a polynomial."]]);
325:
326:
327:
328: /* -----------------------------------------------
329: functions on tests. */
330: /* ------------ Developping functions --------------------- */
331:
332: def RingPoly(vList,weightMatrix,pp) {
333: local new0,tmp,size,n,i,j,newtmp,ringpp,argsize;
334: argsize = Length(Arglist);
335: if (argsize == 1) {
336: sm1("[", vList,
337: "ring_of_polynomials ( ) elimination_order 0 ] define_ring
338: /tmp set ");
1.3 takayama 339: SetRingVariables();
1.1 maekawa 340: return(tmp);
341: } else ;
342: if (argsize == 2) {
343: pp = 0;
344: }
345: pp = IntegerToSm1Integer(pp);
346: size = Length(weightMatrix);
347: new0 = NewVector(size);
348: sm1(" /@@@.indexMode.flag.save @@@.indexMode.flag def ");
349: sm1(" 0 @@@.indexMode ");
350: for (i=0; i<size; i++) {
351: tmp = weightMatrix[i];
352: n = Length(tmp);
353: newtmp = NewVector(n);
354: for (j=1; j<n; j = j+2) {
355: newtmp[j-1] = tmp[j-1];
356: newtmp[j] = IntegerToSm1Integer( tmp[j] );
357: }
358: new0[i] = newtmp;
359: }
1.3 takayama 360: SetRingVariables();
1.1 maekawa 361: ringpp =
362: sm1("[", vList,
363: "ring_of_polynomials ", new0, " weight_vector", pp, " ] define_ring");
364: sm1(" @@@.indexMode.flag.save @@@.indexMode ");
365: return( ringpp );
366: }
367:
368: def IsString(ob) {
369: sm1(ob , " isString /FunctionValue set ");
370: }
371:
372: def IsSm1Integer(ob) {
373: sm1(ob , " isInteger /FunctionValue set ");
1.6 takayama 374: }
375:
376: def IsRing(ob) {
377: sm1(ob , " isRing /FunctionValue set ");
1.1 maekawa 378: }
379:
380:
381: def CancelNumber(rn) {
382: local tmp;
383: sm1(" [(cancel) ",rn," ] mpzext /tmp set ");
384: if (IsInteger(tmp)) return(tmp);
385: sm1(" tmp (denominator) dc (1).. eq { /FunctionValue tmp (numerator) dc def} { /FunctionValue tmp def } ifelse ");
386: }
387:
1.5 takayama 388: def DC_polynomial(obj) {
389: return(DC(obj,"polynomial"));
390: }
1.1 maekawa 391: def DC(obj,key) {
1.5 takayama 392: if (IsArray(obj) && key=="polynomial") {
393: return(Map(obj,"DC_polynomial"));
394: }
1.1 maekawa 395: if (key == "string") { return(ToString(obj)); }
396: else if (key == "integer") { key = "universalNumber"; }
397: else if (key == "sm1integer") { key = "integer"; }
398: else if (key == "polynomial") { key = "poly"; }
399: else ;
400: sm1( obj , key, " data_conversion /FunctionValue set ");
401: }
402:
403: def Transpose(m) {
404: sm1(m, " transpose /FunctionValue set ");
405: }
406:
407: def Save(obj) {
408: sm1(obj, " output ");
409: }
410:
411:
412: def void System(comm) {
413: sm1(comm, " system ");
414: }
415:
416:
417: def IsReducible(f,g) {
418: sm1("[ (isReducible) ",f,g," ] gbext /FunctionValue set ");
419: }
420:
421: def IsPolynomial(f) {
422: sm1(" f isPolynomial /FunctionValue set ");
423: }
424: sm1(" /k00.toric0.mydegree {2 1 roll degree} def ");
425: def Exponent(f,vars) {
426: local n,i,ans;
427: if (f == Poly("0")) return([ ] );
428: sm1(f," /ff.tmp set ", vars ,
429: " {ff.tmp k00.toric0.mydegree (universalNumber) dc }map /FunctionValue set ");
430: }
431: def void Protect(name,level) {
432: local n,str;
433: n = Length(Arglist);
434: if (n == 1) {
435: level = 1;
436: str = AddString(["[(chattr) ",ToString(level)," /",name," ",
437: " ] extension pop "]);
438: /* Println(str); */
439: sm1(" [(parse) ",str ," ] extension pop ");
440: } else if (n ==2) {
441: str = AddString(["[(chattr) ",ToString(level)," /",name," ",
442: " ] extension pop "]);
443: /* Println(str); */
444: sm1(" [(parse) ",str ," ] extension pop ");
445: } else {
446: k00_error("Protect","Arguments must be one or two. ");sm1(" error ");
447: }
448: }
449:
450: def void k00_error(name,msg) {
451: Print("Error in "); Print(name); Print(". ");
452: Println(msg);
453: }
454:
455: def Init(f) {
456: if (IsArray(f)) {
457: return(Map(f,"Init"));
458: } else if (IsPolynomial(f)) {
459: sm1(f," init /FunctionValue set ");
460: } else {
461: k00_error("Init","Argment must be polynomial or an array of polynomials");
462: sm1(" error ");
463: }
464: }
465: HelpAdd(["Init",
466: ["Init(f) returns the initial term of the polynomial <<f>> (polynomial)",
467: "Init(list) returns the array of initial terms of the array of polynomials",
468: "<< list >> (array)"]]);
469:
470: HelpAdd(["NewMatrix",
471: ["NewMatrix(m,n) returns the (m,n)-matrix (array) with the entries 0."]]);
472:
473: def Eliminatev(list,var) /* [(x-y). (y-z).] [(z) ] */
474: {
475: sm1(list, var, " eliminatev /FunctionValue set ");
476: }
477: HelpAdd(["Eliminatev",
478: ["Eliminatev(list,var) prunes polynomials in << list >>(array of polynomials)",
479: "which contains the variables in << var >> ( array of strings )",
480: "Example: Eliminatev([Poly(\" x+h \"),Poly(\" x \")],[ \"h\" ]): "]]);
481:
482: def ReducedBase(base) {
483: sm1( base, " reducedBase /FunctionValue set ");
484: }
485: HelpAdd(["ReducedBase",
486: ["ReducedBase[base] prunes redundant elements in the Grobner basis <<base>> (array)."
487: ]]);
488:
489: def IndexedVariables(name,size) {
490: local result,i,result2;
491: result = [ ];
492: for (i=0; i<size-1; i++) {
493: result = Append(result,Indexed(name,i));
494: result = Append(result,",");
495: }
496: if (size-1 >= 0) {
497: result = Append(result,Indexed(name,size-1));
498: }
499: result2 = Join(["{"],result);
500: result2 = Join(result2,["}"]);
501: return(AddString(result2));
502: }
503: HelpAdd(["IndexedVariables",
504: ["IndexedVariables(name,size) returns the string ",
505: " {name[0],name[1],...,name[size-1]} which can be used as inputs to ",
506: " the function RingD (string name, integer size).",
507: " cf. RingDonIndexedVariables.",
508: " Ex. R = RingD(IndexedVariables(\"a\",3)); ",
509: " h = Poly(\"h\");",
510: " a = NewArray(3);",
511: " for (i=0; i<3; i++) {a[i] = Poly(Indexed(\"a\",i));} ;"]]);
512:
513:
514: def RingDonIndexedVariables(vList, size, weightMatrix,pp) {
515: local myring,tmp,k00_i,argsize,vListD;
516: /* You cannot use these local varialbes as a name of global ring
517: variables. Change these names to names that start with k00_ */
518: argsize = Length(Arglist);
519: if (argsize == 1) {
520: Println("Error (IndexedRingD): ");
521: return(null);
522: }
523: if (argsize == 2) {
524: vListD = AddString(["D",vList]);
525: myring = RingD(IndexedVariables(vList,size));
526: tmp = NewArray(size);
527: for (k00_i=0; k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vList,k00_i));}
528: sm1(vList, " (literal) dc ", tmp, " def ");
529: tmp = NewArray(size);
530: for (k00_i=0; k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vListD,k00_i));}
531: sm1(vListD, " (literal) dc ", tmp, " def ");
532: if (SetRingVariables_Verbose) {
533: Print("Set the global variables ");
534: sm1("[(parse) ",vList," ] extension pop print ");
535: sm1("[(parse) ",vListD," ] extension pop print "); Ln();
536: }else {
537: sm1("[(parse) ",vList," ] extension pop ");
538: sm1("[(parse) ",vListD," ] extension pop ");
539: }
540: return( myring );
541: }
542: if (argsize == 3 || argsize == 4) {
543: if (argsize == 3) { pp = 0; }
544: vListD = AddString(["D",vList]);
545: myring = RingD(IndexedVariables(vList,size),weightMatrix,pp);
546: SetRingVariables();
547: tmp = NewArray(size);
548: for (k00_i=0;k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vList,k00_i));}
549: sm1(vList, " (literal) dc ", tmp, " def ");
550: tmp = NewArray(size);
551: for (k00_i=0;k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vListD,k00_i));}
552: sm1(vListD, " (literal) dc ", tmp, " def ");
553: if (SetRingVariables_Verbose) {
554: Print("Set the global variables ");
555: sm1("[(parse) ",vList," ] extension pop print ");
556: sm1("[(parse) ",vListD," ] extension pop print "); Ln();
557: } else {
558: sm1("[(parse) ",vList," ] extension pop ");
559: sm1("[(parse) ",vListD," ] extension pop ");
560: }
561: return( myring );
562: }
563: return(-1);
564: }
565:
566: def Ringp(f) {
567: sm1(f, " (ring) dc /FunctionValue set ");
568: }
569: HelpAdd(["Ringp",
570: ["Ringp(f) ( polynomial f ) returns the ring to which the polynomial << f >>",
571: "belongs."]]);
572:
573: def Coefficients(f,v) {
574: local ans,exp;
575: ans = sm1(f,v, " coefficients ");
576: exp = ans[0];
577: exp = sm1(exp," { (universalNumber) dc } map ");
578: return([exp,ans[1]]);
579: }
580:
581: def IsInteger(a) {
582: sm1(a , " isUniversalNumber /FunctionValue set ");
583: }
584: HelpAdd(["IsInteger",
585: ["IsInteger(a) returns true if << a >> is an integer (object a).",
586: "It returns false if << a >> is not.",
587: "cf. IsSm1Integer"]]);
588:
589: def IsRational(a) {
590: sm1(a , " isRational /FunctionValue set ");
591: }
592: HelpAdd(["IsRational",
593: ["IsRational(a) returns true if << a >> is a rational (object a).",
594: "It returns false if << a >> is not."]]);
595:
596:
597: def IsDouble(a) {
598: sm1(a , " isDouble /FunctionValue set ");
599: }
600: HelpAdd(["IsDouble",
601: ["IsDouble(a) returns true if << a >> is a double (object a).",
602: "It returns false if << a >> is not."]]);
603:
604:
605: sm1(" /cs { this [ ] Cleards } def ");
606:
607:
608: def Init_w(f,vars,weight) {
609: local w,w2,w3,ans,i,n;
610: if (f == Poly("0")) return( Poly("0") );
611: w = Map(vars,"ToString");
612: w2 = sm1(weight," {$integer$ data_conversion} map ");
613: n = Length(w);
614: w3 = NewArray(n*2);
615: for (i=0; i<n ; i++) {
616: w3[2*i] = w[i]; w3[2*i+1] = w2[i];
617: }
618: ans = sm1(f,w3, " weightv init ");
619: return(ans);
620: }
621:
622: HelpAdd(["Mapto",
623: ["Mapto(obj,ring) parses << obj >> as elements of the << ring >>.",
624: "(ring << ring >>, polynomial << obj >> or array of polynomial << obj >>).",
625: "Ex. R = RingD(\"x,y\"); SetRingVariables();",
626: " f = (x+y)^2; R2 = RingD(\"x,y,z\",[[\"y\",1]]); ",
627: " f2 = Mapto(f,R2); f2: "]]);
628:
629: def Mapto(obj,ring) {
630: local ans,i,n;
631: if (IsArray(obj)) {
632: n = Length(obj);
633: ans = Map(obj,"ToString");
634: for (i=0; i<n; i++) {
635: ans[i] = PolyR(ans[i],ring);
636: }
637: }else{
638: ans = ToString(obj);
639: ans = PolyR(ans,ring);
640: }
641: return(ans);
642: }
643:
644:
645: HelpAdd(["ToDouble",
646: ["ToDouble(f) translates << f >> into double when it is possible",
647: "object << f >>.",
648: "Example: ToDouble([1,1/2,[5]]): "]]);
649: def k00_toDouble(f) { return(DC(f,"double")); }
650: def ToDouble(f) {
651: if (IsArray(f)) return(Map(f,"ToDouble"));
652: if (IsDouble(f)) return(f);
653: return(k00_toDouble(f));
654: }
655:
656:
657: def RingPonIndexedVariables(vList, size, weightMatrix) {
658: local myring,tmp,k00_i,argsize,vListD;
659: /* You cannot use these local varialbes as a name of global ring
660: variables. Change these names to names that start with k00_ */
661: argsize = Length(Arglist);
662: if (argsize == 1) {
663: Println("Error (RingPonIndexedVariables): ");
664: return(null);
665: }
666: if (argsize == 2) {
667: myring = RingPoly(IndexedVariables(vList,size));
668: SetRingVariables();
669: tmp = NewArray(size);
670: for (k00_i=0; k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vList,k00_i));}
671: sm1(vList, " (literal) dc ", tmp, " def ");
672: if (SetRingVariables_Verbose) {
673: Print("Set the global variables ");
674: sm1("[(parse) ",vList," ] extension pop print "); Ln();
675: }else {
676: sm1("[(parse) ",vList," ] extension pop ");
677: }
678: return( myring );
679: }
680: if (argsize == 3) {
681: myring = RingPoly(IndexedVariables(vList,size),weightMatrix);
682: SetRingVariables();
683: tmp = NewArray(size);
684: for (k00_i=0;k00_i<size; k00_i++) {tmp[k00_i]=Poly(Indexed(vList,k00_i));}
685: sm1(vList, " (literal) dc ", tmp, " def ");
686: if (SetRingVariables_Verbose) {
687: Print("Set the global variables ");
688: sm1("[(parse) ",vList," ] extension pop print "); Ln();
689: } else {
690: sm1("[(parse) ",vList," ] extension pop ");
691: }
692: return( myring );
693: }
694: return(-1);
695: }
696:
697: HelpAdd(["RingPonIndexedVariables",
698: ["RingPonIndexedVariables(name,n) defines and returns the ring of",
699: "polynomials",
700: "Q<h, name[0], ..., name[n-1] >",
701: "where <<name>> is a string and <<n>> is an integer.",
702: "Note that this function defines global variables",
703: "h, name[0], ..., name[n-1].",
704: "Example: RingPonIndexedVariables(\"x\",3).",
705: "RingPonIndexedVariables(name,n,w) defines and returns the ring of",
706: "polynomials with the ordering defined by ",
707: "the weight vector <<w>> (array)",
708: "Example: RingPonIndexedVariables(\"x\",3,[[\"x[0]\",1,\"x[2]\",3]])."]]);
709:
710:
711: def Mod(f,n) {
712: if (IsPolynomial(f)) {
713: sm1("[(mod) ",f,n,"] gbext /FunctionValue set ");
714: } else if (IsInteger(f)) { return( Gmp.Mod(f,n) ); }
715: }
716: HelpAdd(["Mod",
717: ["Mod(f,p) returns f modulo n where << f >> (polynomial) and",
718: " << p >> (integer). "]]);
719:
720:
721:
722:
723: def Characteristic(ringp) {
724: local r,p;
725: r = sm1(" [(CurrentRingp)] system_variable ");
726: sm1("[(CurrentRingp) ",ringp, " ] system_variable ");
727: p = sm1("[(P)] system_variable (universalNumber) dc ");
728: sm1("[(CurrentRingp) ",r, " ] system_variable ");
729: return(p);
730: }
731: HelpAdd(["Characteristic",
732: ["Characteristic(ring) returns the characteristic of the << ring >>."
733: ]]);
734:
735: def IsConstant(f) {
736: if (Length(f) > 1) return(false);
737: sm1("[(isConstant) ", f," ] gbext /FunctionValue set ");
738: }
739: HelpAdd(["IsConstant",
740: ["IsConstant(f) returns true if the polynomial << f >> is a constant."
741: ]]);
742:
743: Println("Default ring is Z[x,h]."); x = Poly("x"); h = Poly("h");
744:
745: def Substitute(f,xx,g) {
1.7 ! takayama 746: local tmp, coeff0,ex,i,n,newex,ans;
1.1 maekawa 747: if (IsInteger(f)) return(f);
1.7 ! takayama 748: if (IsArray(f)) {
! 749: n = Length(f);
! 750: ans = NewVector(n);
! 751: for (i=0; i<n; i++) {
! 752: ans[i] = Substitute(f[i],xx,g);
! 753: }
! 754: return(ans);
! 755: }
1.1 maekawa 756: if (! IsPolynomial(f)) {
757: k00_error("Substitute","The first argument must be polynomial.");
758: }
759: tmp = Coefficients(f,xx);
760: coeff0 = tmp[1];
761: ex = tmp[0]; /* [3, 2, 0] */
762: n = Length(ex);
763: newex = NewVector(n);
764: if (n>0) { newex[n-1] = g^ex[n-1]; }
765: for (i=n-2; i>=0; i--) {
766: newex[i] = newex[i+1]*(g^(ex[i]-ex[i+1]));
767: }
768: return(Cancel(coeff0*newex));
769: }
770: HelpAdd(["Substitute",
771: ["Substitute(f,xx,g) replaces << xx >> in << f >> by << g >>.",
772: "This function takes coeffients of << f >> with respect to << xx >>",
773: "and returns the inner product of the vector of coefficients and the vector",
774: "of which elements are g^(corresponding exponent).",
775: "Note that it may cause an unexpected result in non-commutative rings."
776: ]]);
777:
778: def Tag(f) {
779: local ans;
780: if (IsArray(f)) {
781: return(Map(f,"Tag"));
782: }else {
1.4 takayama 783: ans = sm1(f," etag (universalNumber) dc ");
1.1 maekawa 784: return(ans);
785: }
786: }
787: HelpAdd(["Tag",
788: ["Tag(f) returns the datatype tags of f where",
789: "5: string, 9: polynomial, 15: integer(big-num), 16: rational, ",
1.4 takayama 790: "18:double, 257: Error ",
1.1 maekawa 791: "Ex. Tag([Poly(\"0\"), 0]):"
792: ]]);
793:
1.4 takayama 794: def Error(s) {
795: sm1(" s error ");
796: }
797: HelpAdd(["Error",
798: ["Error(s) causes an error and outputs a message s."]]);
1.1 maekawa 799:
800: OutputPrompt ;
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>