source: git/Singular/LIB/general.lib @ 96badc

spielwiese
Last change on this file since 96badc was f937e2, checked in by Hans Schönemann <hannes@…>, 25 years ago
*greuel: binomial, factorial, fibonacci git-svn-id: file:///usr/local/Singular/svn/trunk@3097 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 22.7 KB
Line 
1// $Id: general.lib,v 1.11 1999-06-07 17:25:07 Singular Exp $
2//system("random",787422842);
3//GMG, last modified 30.9.98
4///////////////////////////////////////////////////////////////////////////////
5
6version="$Id: general.lib,v 1.11 1999-06-07 17:25:07 Singular Exp $";
7info="
8LIBRARY:  general.lib   PROCEDURES OF GENERAL TYPE
9
10 A_Z(\"a\",n);            string a,b,... of n comma seperated letters
11 ASCII([n,m]);          string of printable ASCII characters (number n to m)
12 binomial(n,m[,../..]); n choose m (type int), [type string/type number]
13 factorial(n[,../..]);  n factorial (=n!) (type int), [type string/number]
14 fibonacci(n[,p]);      nth Fibonacci number [char p]
15 kmemory();             int = active memory (kilobyte)
16 killall();             kill all user-defined variables
17 number_e(n);           compute exp(1) up to n decimal digits
18 number_pi(n);          compute pi (area of unit circle) up to n digits
19 primes(n,m);           intvec of primes p, n<=p<=m
20 product(../..[,v]);    multiply components of vector/ideal/...[indices v]
21 ringweights(r);        intvec of weights of ring variables of ring r
22 sort(ideal/module);    sort generators according to monomial ordering
23 sum(vector/id/..[,v]); add components of vector/ideal/...[with indices v]
24 which(command);        search for command and return absolute path, if found
25           (parameters in square brackets [] are optional)
26";
27
28LIB "inout.lib";
29///////////////////////////////////////////////////////////////////////////////
30
31proc A_Z (string s,int n)
32"USAGE:   A_Z(\"a\",n);  a any letter, n integer (-26<= n <=26, !=0)
33RETURN:  string of n small (if a is small) or capital (if a is capital)
34         letters, comma seperated, beginning with a, in alphabetical
35         order (or revers alphabetical order if n<0)
36EXAMPLE: example A_Z; shows an example
37"
38{
39  if ( n>=-26 and n<=26 and n!=0 )
40  {
41    string alpha =
42    "a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z,"+
43    "a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z,"+
44    "A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W,X,Y,Z,"+
45    "A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W,X,Y,Z";
46    int ii; int aa;
47    for(ii=1; ii<=51; ii=ii+2)
48    {
49       if( alpha[ii]==s ) { aa=ii; }
50    }
51    if ( aa==0)
52    {
53      for(ii=105; ii<=155; ii=ii+2)
54      {
55        if( alpha[ii]==s ) { aa=ii; }
56      }
57    }
58    if( aa!=0 )
59    {
60      string out;
61      if (n > 0) { out = alpha[aa,2*(n)-1];  return (out); }
62      if (n < 0)
63      {
64        string beta =
65        "z,y,x,w,v,u,t,s,r,q,p,o,n,m,l,k,j,i,h,g,f,e,d,c,b,a,"+
66        "z,y,x,w,v,u,t,s,r,q,p,o,n,m,l,k,j,i,h,g,f,e,d,c,b,a,"+
67        "Z,Y,X,W,V,U,T,S,R,Q,P,O,N,M,L,K,J,I,H,G,F,E,D,C,B,A,"+
68        "Z,Y,X,W,V,U,T,S,R,Q,P,O,N,M,L,K,J,I,H,G,F,E,D,C,B,A";
69        if ( aa < 52 ) { aa=52-aa; }
70        if ( aa > 104 ) { aa=260-aa; }
71        out = beta[aa,2*(-n)-1]; return (out);
72      }
73    }
74  }
75}
76example
77{ "EXAMPLE:"; echo = 2;
78   A_Z("c",5);
79   A_Z("Z",-5);
80   string sR = "ring R = (0,"+A_Z("A",6)+"),("+A_Z("a",10)+"),dp;";
81   sR;
82   execute sR;
83   R;
84}
85///////////////////////////////////////////////////////////////////////////////
86proc ASCII (list #)
87"USAGE:   ASCII([n,m]); n,m= integers (32 <= n <= m <= 126)
88RETURN:   printable ASCII characters (no native language support)
89          ASCII():    string of  all ASCII characters with its numbers,
90                      no return value
91          ASCII(n):   string, n-th ASCII charakter
92          ASCII(n,m): list, n-th up to m-th ASCII character (inclusive)
93EXAMPLE: example ASCII; shows an example
94"
95{
96  string s1 =
97 "     !    \"    #    $    %    &    '    (    )    *    +    ,    -    .
9832   33   34   35   36   37   38   39   40   41   42   43   44   45   46
99
100/    0    1    2    3    4    5    6    7    8    9    :    ;    <    =
10147   48   49   50   51   52   53   54   55   56   57   58   59   60   61
102
103>    ?    @    A    B    C    D    E    F    G    H    I    J    K    L
10462   63   64   65   66   67   68   69   70   71   72   73   74   75   76
105
106M    N    O    P    Q    R    S    T    U    V    W    X    Y    Z    [
10777   78   79   80   81   82   83   84   85   86   87   88   89   90   91
108
109\\    ]    ^    _    `    a    b    c    d    e    f    g    h    i    j
11092   93   94   95   96   97   98   99  100  101  102  103  104  105  10
111
112k    l    m    n    o    p    q    r    s    t    u    v    w    x    y
113107  108  109  110  111  112  113  114  115  116  117  118  119  120  121
114
115z    {    |    }    ~
116122  123  124  125  126 ";
117
118   string s2 =
119 " !\"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklmnopqrstuvwxyz{|}~";
120
121   if ( size(#) == 0 )
122   {
123      return(s1);
124   }
125   if ( size(#) == 1 )
126   {
127      return( s2[#[1]-31] );
128   }
129   if ( size(#) == 2 )
130   {
131      return( s2[#[1]-31,#[2]-#[1]+1] );
132   }
133}
134example
135{ "EXAMPLE:"; echo = 2;
136   ASCII();"";
137   ASCII(42);
138   ASCII(32,126);
139}
140///////////////////////////////////////////////////////////////////////////////
141
142proc binomial (def n, int k, list #)
143"USAGE:   binomial(n,k[,p]); n,k,p integers
144RETURN:  binomial(n,k); binomial coefficient n choose k,
145         of type number if n is of type number (computed in char(basering)),
146         of type int if n is of type int (machine integer, limited size!)
147         binomial(n,k,p);  n choose k in char p, of type string
148EXAMPLE: example binomial; shows an example
149"
150{
151   if ( size(#)==0 )
152   {
153      if ( typeof(n)=="number" ) { number rr=1; }
154      else { int rr=1; }
155   }
156   if ( typeof(#[1])=="int") { ring bin = #[1],x,dp; number rr=1; }
157   if ( size(#)==0 or typeof(#[1])=="int" )
158   {
159      def r = rr;
160      if ( k<=0 or k>n ) { return((k==0)*r); }
161      if ( k>n-k ) { k = n-k; }
162      int l;
163      for (l=1; l<=k; l=l+1 )
164      {
165         r=r*(n+1-l)/l;
166      }
167      if ( typeof(#[1])=="int" ) { return(string(r)); }
168      return(r);
169   }
170}
171example
172{ "EXAMPLE:"; echo = 2;
173   int b1 = binomial(10,7); b1;
174   binomial(137,17,0);
175   ring t = 0,x,dp;
176   number b2 = binomial(number(137),17); b2;
177}
178///////////////////////////////////////////////////////////////////////////////
179
180proc factorial (def n)
181"USAGE:   factorial(n);  n = integer
182RETURN:  factorial(n); n! in char 0, of type string if n is of type int
183         n! of type number, computed in char(basering) if n is of type number
184EXAMPLE: example factorial; shows an example
185"
186{
187   int t,l;
188   if ( typeof(n)=="number" ) { number r=1; }
189   else { ring R = 0,x,dp; number r=1; t=1; }
190   for (l=2; l<=n; l=l+1)
191   {
192      r=r*l;
193   }
194   if ( t==1 ) { return(string(r)); }
195   return(r);
196}
197example
198{ "EXAMPLE:"; echo = 2;
199   factorial(37);
200   ring r1 = 32003,(x,y,z),ds;
201   number p = factorial(number(37)); p;
202}
203///////////////////////////////////////////////////////////////////////////////
204
205proc fibonacci (def n)
206"USAGE:   fibonacci(n);  (n integer)
207RETURN:  fibonacci(n); nth Fibonacci number,
208            f(0)=f(1)=1, f(i+1)=f(i-1)+f(i)
209         of type string if n is of type int
210         of type number computed in char(basering) if n is of type number
211EXAMPLE: example fibonacci; shows an example
212"
213{
214   int ii,t;
215   if ( typeof(n)=="number" ) { number f,g,h=1,1,1; }
216   else { ring fibo = 0,x,dp; number f,g,h=1,1,1; t=1; }
217   for (ii=3; ii<=n; ii=ii+1)
218   {
219      h = f+g; f = g; g = h;
220    }
221   if ( t==1 ) { return(string(h)); }
222   return(h);
223}
224example
225{ "EXAMPLE:"; echo = 2;
226   fibonacci(37);
227   ring r = 17,x,dp;
228   number b = fibonacci(number(37)); b;
229}
230///////////////////////////////////////////////////////////////////////////////
231
232proc kmemory ()
233"USAGE:   kmemory();
234RETURN:  memory used by active variables, of type int (in kilobyte)
235EXAMPLE: example kmemory; shows an example
236"
237{
238  if ( voice==2 ) { "// memory used by active variables (kilobyte):"; }
239   return ((memory(0)+1023)/1024);
240}
241example
242{ "EXAMPLE:"; echo = 2;
243   kmemory();
244}
245///////////////////////////////////////////////////////////////////////////////
246
247proc killall
248"USAGE:   killall(); (no parameter)
249         killall(\"type_name\");
250         killall(\"not\", \"type_name\");
251COMPUTE: killall(); kills all user-defined variables but not loaded procedures
252         killall(\"type_name\"); kills all user-defined variables, of type \"type_name\"
253         killall(\"not\", \"type_name\"); kills all user-defined
254         variables, except those of type \"type_name\" and except loaded procedures
255RETURN:  no return value
256NOTE:    killall should never be used inside a procedure
257EXAMPLE: example killall; shows an example AND KILLS ALL YOUR VARIABLES
258"
259{
260   list L=names(); int joni=size(L);
261   if( size(#)==0 )
262   {
263      for ( ; joni>0; joni-- )
264      {
265         if( L[joni]!="LIB" and typeof(`L[joni]`)!="proc" ) { kill `L[joni]`; }
266      }
267   }
268   else
269   {
270     if( size(#)==1 )
271     {
272       if( #[1] == "proc" )
273       {
274          for ( joni=size(L); joni>0; joni-- )
275          {
276             if( L[joni]=="LIB" or typeof(`L[joni]`)=="proc" )
277               { kill `L[joni]`; }
278          }
279       }
280       else
281       {
282          for ( ; joni>2; joni-- )
283          {
284            if(typeof(`L[joni]`)==#[1] and L[joni]!="LIB" and typeof(`L[joni]`)!="proc") { kill `L[joni]`; }
285          }
286        }
287     }
288     else
289     {
290        for ( ; joni>2; joni-- )
291        {
292          if(typeof(`L[joni]`)!=#[2] and L[joni]!="LIB" and typeof(`L[joni]`)!="proc") { kill `L[joni]`; }
293        }
294     }
295  }
296  return();
297}
298example
299{ "EXAMPLE:"; echo = 2;
300   ring rtest; ideal i=x,y,z; number n=37; string str="hi"; int j = 3;
301   export rtest,i,n,str,j;     //this makes the local variables global
302   listvar(all);
303   killall("string"); // kills all string variables
304   listvar(all);
305   killall("not", "int"); // kills all variables except int's (and procs)
306   listvar(all);
307   killall(); // kills all vars except loaded procs
308   listvar(all);
309}
310///////////////////////////////////////////////////////////////////////////////
311
312proc number_e (int n)
313"USAGE:   number_e(n);  n integer
314COMPUTE: Euler number e=exp(1) up to n decimal digits (no rounding)
315         by A.H.J. Sale's algorithm
316RETURN:  - string of exp(1) if no basering of char 0 is defined;
317         - exp(1), of type number, if a basering of char 0 is defined and
318         display its decimal format
319EXAMPLE: example number_e; shows an example
320"
321{
322   int i,m,s,t;
323   intvec u,e;
324   u[n+2]=0; e[n+1]=0; e=e+1;
325   if( defined(basering) )
326   {
327      if( char(basering)==0 ) { number r=2; t=1; }
328   }
329   string result = "2.";
330   for( i=1; i<=n+1; i=i+1 )
331   {
332      e = e*10;
333      for( m=n+1; m>=1; m=m-1 )
334      {
335         s    = e[m]+u[m+1];
336         u[m] = s div (m+1);
337         e[m] = s%(m+1);
338      }
339      result = result+string(u[1]);
340      if( t==1 ) { r = r+number(u[1])/number(10)^i; }
341   }
342   if( t==1 ) { "//",result[1,n+1]; return(r); }
343   return(result[1,n+1]);
344}
345example
346{ "EXAMPLE:"; echo = 2;
347   number_e(15);
348   ring R = 0,t,lp;
349   number e = number_e(10);
350   e;
351}
352///////////////////////////////////////////////////////////////////////////////
353
354proc number_pi (int n)
355"USAGE:   number_pi(n);  n positive integer
356COMPUTE: pi (area of unit circle) up to n decimal digits (no rounding)
357         by algorithm of S. Rabinowitz
358RETURN:  - string of pi if no basering of char 0 is defined,
359         - pi, of type number, if a basering of char 0 is defined and display
360         its decimal format
361EXAMPLE: example number_pi; shows an example
362"
363{
364   int i,m,t,e,q,N;
365   intvec r,p,B,Prelim;
366   string result,prelim;
367   N = (10*n) div 3 + 2;
368   p[N+1]=0; p=p+2; r=p;
369   for( i=1; i<=N+1; i=i+1 ) { B[i]=2*i-1; }
370   if( defined(basering) )
371   {
372      if( char(basering)==0 ) { number pi; number pri; t=1; }
373   }
374   for( i=0; i<=n; i=i+1 )
375   {
376      p = r*10;
377      e = p[N+1];
378      for( m=N+1; m>=2; m=m-1 )
379      {
380         r[m] = e%B[m];
381         q    = e div B[m];
382         e    = q*(m-1)+p[m-1];
383      }
384      r[1] = e%10;
385      q    = e div 10;
386      if( q!=10 and q!=9 )
387      {
388         result = result+prelim;
389         Prelim = q;
390         prelim = string(q);
391      }
392      if( q==9 )
393      {
394         Prelim = Prelim,9;
395         prelim = prelim+"9";
396      }
397      if( q==10 )
398      {
399         Prelim = (Prelim+1)-((Prelim+1) div 10)*10;
400         for( m=size(Prelim); m>0; m=m-1)
401         {
402            prelim[m] = string(Prelim[m]);
403         }
404         result = result+prelim;
405         if( t==1 ) { pi=pi+pri; }
406         Prelim = 0;
407         prelim = "0";
408      }
409      if( t==1 ) { pi=pi+number(q)/number(10)^i; }
410   }
411   result = result,prelim[1];
412   result = "3."+result[2,n-1];
413   if( t==1 ) { "//",result; return(pi); }
414   return(result);
415}
416example
417{ "EXAMPLE:"; echo = 2;
418   number_pi(5);
419   ring r = 0,t,lp;
420   number pi = number_pi(6);
421   pi;
422}
423///////////////////////////////////////////////////////////////////////////////
424
425proc primes (int n, int m)
426"USAGE:   primes(n,m);  n,m integers
427RETURN:  intvec, consisting of all primes p, prime(n)<=p<=m, in increasing
428         order if n<=m, resp. prime(m)<=p<=n, in decreasing order if m<n
429NOTE:    prime(n); returns the biggest prime number <= n (if n>=2, else 2)
430EXAMPLE: example primes; shows an example
431"
432{  int change;
433   if ( n>m ) { change=n; n=m ; m=change; change=1; }
434   int q,p = prime(m),prime(n); intvec v = q; q = q-1;
435   while ( q>=p ) { q = prime(q); v = q,v; q = q-1; }
436   if ( change==1 ) { v = v[size(v)..1]; }
437   return(v);
438}
439example
440{  "EXAMPLE:"; echo = 2;
441   primes(50,100);
442   intvec v = primes(37,1); v;
443}
444///////////////////////////////////////////////////////////////////////////////
445
446proc product (id, list #)
447"USAGE:    product(id[,v]); id=ideal/vector/module/matrix
448          resp.id=intvec/intmat, v=intvec (e.g. v=1..n, n=integer)
449RETURN:   poly resp. int which is the product of all entries of id, with index
450          given by v (default: v=1..number of entries of id)
451NOTE:     id is treated as a list of polys resp. integers. A module m is
452          identified with corresponding matrix M (columns of M generate m)
453EXAMPLE:  example product; shows an example
454"
455{
456   int n,j;
457   if( typeof(id)=="poly" or typeof(id)=="ideal" or typeof(id)=="vector"
458       or typeof(id)=="module" or typeof(id)=="matrix" )
459   {
460      ideal i = ideal(matrix(id));
461      if( size(#)!=0 ) { i = i[#[1]]; }
462      n = ncols(i); poly f=1;
463   }
464   if( typeof(id)=="int" or typeof(id)=="intvec" or typeof(id)=="intmat" )
465   {
466      if ( typeof(id) == "int" ) { intmat S =id; }
467      else { intmat S = intmat(id); }
468      intvec i = S[1..nrows(S),1..ncols(S)];
469      if( size(#)!=0 ) { i = i[#[1]]; }
470      n = size(i); int f=1;
471   }
472   for( j=1; j<=n; j=j+1 ) { f=f*i[j]; }
473   return(f);
474}
475example
476{  "EXAMPLE:"; echo = 2;
477   ring r= 0,(x,y,z),dp;
478   ideal m = maxideal(1);
479   product(m);
480   matrix M[2][3] = 1,x,2,y,3,z;
481   product(M);
482   intvec v=2,4,6;
483   product(M,v);
484   intvec iv = 1,2,3,4,5,6,7,8,9;
485   v=1..5,7,9;
486   product(iv,v);
487   intmat A[2][3] = 1,1,1,2,2,2;
488   product(A,3..5);
489}
490///////////////////////////////////////////////////////////////////////////////
491
492proc ringweights (r)
493"USAGE:   ringweights(r); r ring
494RETURN:  intvec of weights of ring variables. If, say, x(1),...,x(n) are the
495         variables of the ring r, in this order, the resulting intvec is
496         deg(x(1)),...,deg(x(n)) where deg denotes the weighted degree if
497         the monomial ordering of r has only one block of type ws,Ws,wp or Wp.
498NOTE:    In all other cases, in particular if there is more than one block,
499         the resulting intvec is 1,...,1
500EXAMPLE: example ringweights; shows an example
501"
502{
503   int i; intvec v; setring r;
504   for (i=1; i<=nvars(basering); i=i+1) { v[i] = deg(var(i)); }
505   return(v);
506}
507example
508{ "EXAMPLE:"; echo = 2;
509   ring r1=32003,(x,y,z),wp(1,2,3);
510   ring r2=32003,(x,y,z),Ws(1,2,3);
511   ring r=0,(x,y,u,v),lp;
512   intvec vr=ringweights(r1); vr;
513   ringweights(r2);
514   ringweights(r);
515}
516///////////////////////////////////////////////////////////////////////////////
517
518proc sort (id, list #)
519"USAGE:   sort(id[v,o,n]); id=ideal/module/intvec/list (of intvec's or int's)
520         sort may be called with 1, 2 or 3 arguments in the following way:
521         -  sort(id[v,n]); v=intvec of positive integers, n=integer,
522         -  sort(id[o,n]); o=string (any allowed ordstr of a ring), n=integer
523RETURN:  a list of two elements:
524         [1]: object of same type as input but sorted in the following manner:
525           - if id=ideal/module: generators of id are sorted w.r.t. intvec v
526             (id[v[1]] becomes 1-st, id[v[2]]  2-nd element, etc.). If no v is
527             present, id is sorted w.r.t. ordering o (if o is given) or w.r.t.
528             actual monomial ordering (if no o is given):
529                    generators with smaller leading term come first
530             (e.g. sort(id); sorts w.r.t actual monomial ordering)
531           - if id=list of intvec's or int's: consider a list element, say
532             id[1]=3,2,5, as exponent vector of the monomial x^3*y^2*z^5;
533             the corresponding monomials are ordered w.r.t. intvec v (s.a.).
534             If no v is present, the monomials are sorted w.r.t. ordering o
535             (if o is given) or w.r.t. lexicographical ordering (if no o is
536             given). The corresponding ordered list of exponent vectors is
537             returned.
538             (e.g. sort(id); sorts lexicographically, smaller int's come first)
539             WARNING: Since negative exponents create the 0 polynomial in
540             Singular, id should not contain negative integers: the result
541             might not be as expected
542           - if id=intvec: id is treated as list of integers
543           - if n!=0 the ordering is inverse, i.e. w.r.t. v(size(v)..1)
544             default: n=0
545         [2]: intvec, describing the permutation of the input (hence [2]=v if
546             v is given (with positive integers)
547NOTE:    If v is given id may be any simply indexed object (e.g. any list or
548         string); if v[i]<0 and i<=size(id) v[i] is set internally to i;
549         entries of v must be pairwise distinct to get a permutation if id.
550         Zero generators of ideal/module are deleted
551EXAMPLE: example sort; shows an example
552"
553{
554   int ii,jj,s,n = 0,0,1,0;
555   intvec v;
556   if ( defined(basering) ) { def P = basering; }
557   if ( size(#)==0 and (typeof(id)=="ideal" or typeof(id)=="module") )
558   {
559      id = simplify(id,2);
560      for ( ii=1; ii<size(id); ii++ )
561      {
562         if ( id[ii]!=id[ii+1] ) { break;}
563      }
564      if ( ii != size(id) ) { v = sortvec(id); }
565      else  { v = size(id)..1; }
566   }
567   if ( size(#)>=1 and (typeof(id)=="ideal" or typeof(id)=="module") )
568   {
569      if ( typeof(#[1])=="string" )
570      {
571         execute "ring r1 =("+charstr(P)+"),("+varstr(P)+"),("+#[1]+");";
572         def i = imap(P,id);
573         v = sortvec(i);
574         setring P;
575         n=2;
576      }
577   }
578   if ( typeof(id)=="intvec" or typeof(id)=="list" and n==0 )
579   {
580      string o;
581      if ( size(#)==0 ) { o = "lp"; n=1; }
582      if ( size(#)>=1 )
583      {
584         if ( typeof(#[1])=="string" ) { o = #[1]; n=1; }
585      }
586   }
587   if ( typeof(id)=="intvec" or typeof(id)=="list" and n==1 )
588   {
589      if ( typeof(id)=="list" )
590      {
591         for (ii=1; ii<=size(id); ii++)
592         {
593            if (typeof(id[ii]) != "intvec" and typeof(id[ii]) != "int")
594               { "// list elements must be intvec/int"; return(); }
595            else
596               { s=size(id[ii])*(s < size(id[ii])) + s*(s >= size(id[ii])); }
597         }
598      }
599      execute "ring r=0,x(1..s),("+o+");";
600      ideal i;
601      poly f;
602      for (ii=1; ii<=size(id); ii++)
603      {
604         f=1;
605         for (jj=1; jj<=size(id[ii]); jj++)
606         {
607            f=f*x(jj)^(id[ii])[jj];
608         }
609         i[ii]=f;
610      }
611      v = sort(i)[2];
612   }
613   if ( size(#)!=0 and n==0 ) { v = #[1]; }
614   if( size(#)==2 )
615   {
616      if ( #[2] != 0 ) { v = v[size(v)..1]; }
617   }
618   s = size(v);
619   if( size(id) < s ) { s = size(id); }
620   def m = id;
621   if ( size(m) != 0 )
622   {
623      for ( jj=1; jj<=s; jj=jj+1)
624      {
625         if ( v[jj]<=0 ) { v[jj]=jj; }
626         m[jj] = id[v[jj]];
627      }
628   }
629   if ( v == 0 ) { v = 1; }
630   list L=m,v;
631   return(L);
632}
633example
634{  "EXAMPLE:"; echo = 2;
635   ring r0 = 0,(x,y,z),lp;
636   ideal i = x3,y3,z3,x2z,x2y,y2z,y2x,z2y,z2x,xyz;
637   show(sort(i));"";
638   show(sort(i,"wp(1,2,3)"));"";
639   intvec v=10..1;
640   show(sort(i,v));"";
641   show(sort(i,v,1));"";   // should be the identity
642   ring r1  = 0,t,ls;
643   ideal j = t14,t6,t28,t20,t12,t34,t26,t18,t40,t32,t24,t38,t30,t36;
644   show(sort(j)[1]);"";
645   show(sort(j,"lp")[1]);"";
646   list L =1,5..8,10,2,8..5,8,3..10;
647   sort(L)[1];"";          // sort L lexicographically
648   sort(L,"Dp",1)[1];      // sort L w.r.t (total sum, reverse lex)
649}
650///////////////////////////////////////////////////////////////////////////////
651
652proc sum (id, list #)
653"USAGE:    sum(id[,v]); id=ideal/vector/module/matrix resp. id=intvec/intmat,
654                       v=intvec (e.g. v=1..n, n=integer)
655RETURN:   poly resp. int which is the sum of all entries of id, with index
656          given by v (default: v=1..number of entries of id)
657NOTE:     id is treated as a list of polys resp. integers. A module m is
658          identified with corresponding matrix M (columns of M generate m)
659EXAMPLE:  example sum; shows an example
660"
661{
662   if( typeof(id)=="poly" or typeof(id)=="ideal" or typeof(id)=="vector"
663       or typeof(id)=="module" or typeof(id)=="matrix" )
664   {
665      ideal i = ideal(matrix(id));
666      if( size(#)!=0 ) { i = i[#[1]]; }
667      matrix Z = matrix(i);
668   }
669   if( typeof(id)=="int" or typeof(id)=="intvec" or typeof(id)=="intmat" )
670   {
671      if ( typeof(id) == "int" ) { intmat S =id; }
672      else { intmat S = intmat(id); }
673      intvec i = S[1..nrows(S),1..ncols(S)];
674      if( size(#)!=0 ) { i = i[#[1]]; }
675      intmat Z=transpose(i);
676   }
677   intvec v; v[ncols(Z)]=0; v=v+1;
678   return((Z*v)[1,1]);
679}
680example
681{  "EXAMPLE:"; echo = 2;
682   ring r= 0,(x,y,z),dp;
683   vector pv = [xy,xz,yz,x2,y2,z2];
684   sum(pv);
685   //sum(pv,2..5);
686   //matrix M[2][3] = 1,x,2,y,3,z;
687   //sum(M);
688   //intvec w=2,4,6;
689   //sum(M,w);
690   //intvec iv = 1,2,3,4,5,6,7,8,9;
691   //w=1..5,7,9;
692   //sum(iv,w);
693   //intmat m[2][3] = 1,1,1,2,2,2;
694   //sum(m,3..4);
695}
696///////////////////////////////////////////////////////////////////////////////
697
698proc which (command)
699"USAGE:    which(command); command = string expression
700RETURN:   Absolute pathname of command, if found in search path.
701          Empty string, otherwise.
702NOTE:     Based on the Unix command 'which'.
703EXAMPLE:  example which; shows an example
704"
705{
706   int rs;
707   int i;
708   string fn = "/tmp/which_" + string(system("pid"));
709   string pn;
710   if( typeof(command) != "string")
711   {
712     return (pn);
713   }
714   i = system("sh", "which " + command + " > " + fn);
715   pn = read(fn);
716   pn[size(pn)] = "";
717   i = 1;
718   while ((pn[i] != " ") and (pn[i] != ""))
719   {
720     i = i+1;
721   }
722   if (pn[i] == " ") {pn[i] = "";}
723   rs = system("sh", "ls " + pn + " > " + fn + " 2>&1 ");
724   i = system("sh", "rm " + fn);
725   if (rs == 0) {return (pn);}
726   else
727   {
728     print (command + " not found ");
729     return ("");
730   }
731}
732example
733{  "EXAMPLE:"; echo = 2;
734    which("Singular");
735}
736///////////////////////////////////////////////////////////////////////////////
Note: See TracBrowser for help on using the repository browser.