source: git/Singular/LIB/general.lib @ d694de

spielwiese
Last change on this file since d694de was d694de, checked in by Gert-Martin Greuel <greuel@…>, 25 years ago
* extension of proc kmemory git-svn-id: file:///usr/local/Singular/svn/trunk@3146 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 23.3 KB
Line 
1// $Id: general.lib,v 1.12 1999-06-18 13:47:27 greuel Exp $
2//system("random",787422842);
3//GMG, last modified 18.6.99
4///////////////////////////////////////////////////////////////////////////////
5
6version="$Id: general.lib,v 1.12 1999-06-18 13:47:27 greuel 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([n]);          active [allocated] memory in 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 (list #)
233"USAGE:   kmemory([n]); n = int
234RETURN:  memory in kilobyte of type int
235         n=0: memory used by active variables (same as no parameters)
236         n=1: total memory allocated by Singular
237         n=2: difference between top and init memory adress (sbrk memory)
238         n!=0,1,2: 0
239DISPLAY: detailed information about allocated and used memory if n!=0,1,2
240NOTE:    kmemory uses internal function 'memory' to compute kilobyte, and
241         is the same as 'memory' for n!=0,1,2
242EXAMPLE: example kmemory; shows an example
243"
244{
245   int n;
246   if (size(#) != 0)
247   {
248     n=#[1];
249   }
250   
251  if ( n==0)
252  { dbprint(printlevel-voice+3,
253    "// memory used, at the moment, by active variables (kilobyte):"); }
254  if ( n==1 )
255  { dbprint(printlevel-voice+3,
256    "// total memory allocated, at the moment, by SINGULAR (kilobyte):"); }
257   return ((memory(n)+1023)/1024);
258}
259example
260{ "EXAMPLE:"; echo = 2;
261   kmemory();
262   kmemory(1);
263}
264///////////////////////////////////////////////////////////////////////////////
265
266proc killall
267"USAGE:   killall(); (no parameter)
268         killall(\"type_name\");
269         killall(\"not\", \"type_name\");
270COMPUTE: killall(); kills all user-defined variables but not loaded procedures
271         killall(\"type_name\"); kills all user-defined variables, of type \"type_name\"
272         killall(\"not\", \"type_name\"); kills all user-defined
273         variables, except those of type \"type_name\" and except loaded procedures
274RETURN:  no return value
275NOTE:    killall should never be used inside a procedure
276EXAMPLE: example killall; shows an example AND KILLS ALL YOUR VARIABLES
277"
278{
279   list L=names(); int joni=size(L);
280   if( size(#)==0 )
281   {
282      for ( ; joni>0; joni-- )
283      {
284         if( L[joni]!="LIB" and typeof(`L[joni]`)!="proc" ) { kill `L[joni]`; }
285      }
286   }
287   else
288   {
289     if( size(#)==1 )
290     {
291       if( #[1] == "proc" )
292       {
293          for ( joni=size(L); joni>0; joni-- )
294          {
295             if( L[joni]=="LIB" or typeof(`L[joni]`)=="proc" )
296               { kill `L[joni]`; }
297          }
298       }
299       else
300       {
301          for ( ; joni>2; joni-- )
302          {
303            if(typeof(`L[joni]`)==#[1] and L[joni]!="LIB" and typeof(`L[joni]`)!="proc") { kill `L[joni]`; }
304          }
305        }
306     }
307     else
308     {
309        for ( ; joni>2; joni-- )
310        {
311          if(typeof(`L[joni]`)!=#[2] and L[joni]!="LIB" and typeof(`L[joni]`)!="proc") { kill `L[joni]`; }
312        }
313     }
314  }
315  return();
316}
317example
318{ "EXAMPLE:"; echo = 2;
319   ring rtest; ideal i=x,y,z; number n=37; string str="hi"; int j = 3;
320   export rtest,i,n,str,j;     //this makes the local variables global
321   listvar(all);
322   killall("string"); // kills all string variables
323   listvar(all);
324   killall("not", "int"); // kills all variables except int's (and procs)
325   listvar(all);
326   killall(); // kills all vars except loaded procs
327   listvar(all);
328}
329///////////////////////////////////////////////////////////////////////////////
330
331proc number_e (int n)
332"USAGE:   number_e(n);  n integer
333COMPUTE: Euler number e=exp(1) up to n decimal digits (no rounding)
334         by A.H.J. Sale's algorithm
335RETURN:  - string of exp(1) if no basering of char 0 is defined;
336         - exp(1), of type number, if a basering of char 0 is defined and
337         display its decimal format
338EXAMPLE: example number_e; shows an example
339"
340{
341   int i,m,s,t;
342   intvec u,e;
343   u[n+2]=0; e[n+1]=0; e=e+1;
344   if( defined(basering) )
345   {
346      if( char(basering)==0 ) { number r=2; t=1; }
347   }
348   string result = "2.";
349   for( i=1; i<=n+1; i=i+1 )
350   {
351      e = e*10;
352      for( m=n+1; m>=1; m=m-1 )
353      {
354         s    = e[m]+u[m+1];
355         u[m] = s div (m+1);
356         e[m] = s%(m+1);
357      }
358      result = result+string(u[1]);
359      if( t==1 ) { r = r+number(u[1])/number(10)^i; }
360   }
361   if( t==1 ) { "//",result[1,n+1]; return(r); }
362   return(result[1,n+1]);
363}
364example
365{ "EXAMPLE:"; echo = 2;
366   number_e(15);
367   ring R = 0,t,lp;
368   number e = number_e(10);
369   e;
370}
371///////////////////////////////////////////////////////////////////////////////
372
373proc number_pi (int n)
374"USAGE:   number_pi(n);  n positive integer
375COMPUTE: pi (area of unit circle) up to n decimal digits (no rounding)
376         by algorithm of S. Rabinowitz
377RETURN:  - string of pi if no basering of char 0 is defined,
378         - pi, of type number, if a basering of char 0 is defined and display
379         its decimal format
380EXAMPLE: example number_pi; shows an example
381"
382{
383   int i,m,t,e,q,N;
384   intvec r,p,B,Prelim;
385   string result,prelim;
386   N = (10*n) div 3 + 2;
387   p[N+1]=0; p=p+2; r=p;
388   for( i=1; i<=N+1; i=i+1 ) { B[i]=2*i-1; }
389   if( defined(basering) )
390   {
391      if( char(basering)==0 ) { number pi; number pri; t=1; }
392   }
393   for( i=0; i<=n; i=i+1 )
394   {
395      p = r*10;
396      e = p[N+1];
397      for( m=N+1; m>=2; m=m-1 )
398      {
399         r[m] = e%B[m];
400         q    = e div B[m];
401         e    = q*(m-1)+p[m-1];
402      }
403      r[1] = e%10;
404      q    = e div 10;
405      if( q!=10 and q!=9 )
406      {
407         result = result+prelim;
408         Prelim = q;
409         prelim = string(q);
410      }
411      if( q==9 )
412      {
413         Prelim = Prelim,9;
414         prelim = prelim+"9";
415      }
416      if( q==10 )
417      {
418         Prelim = (Prelim+1)-((Prelim+1) div 10)*10;
419         for( m=size(Prelim); m>0; m=m-1)
420         {
421            prelim[m] = string(Prelim[m]);
422         }
423         result = result+prelim;
424         if( t==1 ) { pi=pi+pri; }
425         Prelim = 0;
426         prelim = "0";
427      }
428      if( t==1 ) { pi=pi+number(q)/number(10)^i; }
429   }
430   result = result,prelim[1];
431   result = "3."+result[2,n-1];
432   if( t==1 ) { "//",result; return(pi); }
433   return(result);
434}
435example
436{ "EXAMPLE:"; echo = 2;
437   number_pi(5);
438   ring r = 0,t,lp;
439   number pi = number_pi(6);
440   pi;
441}
442///////////////////////////////////////////////////////////////////////////////
443
444proc primes (int n, int m)
445"USAGE:   primes(n,m);  n,m integers
446RETURN:  intvec, consisting of all primes p, prime(n)<=p<=m, in increasing
447         order if n<=m, resp. prime(m)<=p<=n, in decreasing order if m<n
448NOTE:    prime(n); returns the biggest prime number <= n (if n>=2, else 2)
449EXAMPLE: example primes; shows an example
450"
451{  int change;
452   if ( n>m ) { change=n; n=m ; m=change; change=1; }
453   int q,p = prime(m),prime(n); intvec v = q; q = q-1;
454   while ( q>=p ) { q = prime(q); v = q,v; q = q-1; }
455   if ( change==1 ) { v = v[size(v)..1]; }
456   return(v);
457}
458example
459{  "EXAMPLE:"; echo = 2;
460   primes(50,100);
461   intvec v = primes(37,1); v;
462}
463///////////////////////////////////////////////////////////////////////////////
464
465proc product (id, list #)
466"USAGE:    product(id[,v]); id=ideal/vector/module/matrix
467          resp.id=intvec/intmat, v=intvec (e.g. v=1..n, n=integer)
468RETURN:   poly resp. int which is the product of all entries of id, with index
469          given by v (default: v=1..number of entries of id)
470NOTE:     id is treated as a list of polys resp. integers. A module m is
471          identified with corresponding matrix M (columns of M generate m)
472EXAMPLE:  example product; shows an example
473"
474{
475   int n,j;
476   if( typeof(id)=="poly" or typeof(id)=="ideal" or typeof(id)=="vector"
477       or typeof(id)=="module" or typeof(id)=="matrix" )
478   {
479      ideal i = ideal(matrix(id));
480      if( size(#)!=0 ) { i = i[#[1]]; }
481      n = ncols(i); poly f=1;
482   }
483   if( typeof(id)=="int" or typeof(id)=="intvec" or typeof(id)=="intmat" )
484   {
485      if ( typeof(id) == "int" ) { intmat S =id; }
486      else { intmat S = intmat(id); }
487      intvec i = S[1..nrows(S),1..ncols(S)];
488      if( size(#)!=0 ) { i = i[#[1]]; }
489      n = size(i); int f=1;
490   }
491   for( j=1; j<=n; j=j+1 ) { f=f*i[j]; }
492   return(f);
493}
494example
495{  "EXAMPLE:"; echo = 2;
496   ring r= 0,(x,y,z),dp;
497   ideal m = maxideal(1);
498   product(m);
499   matrix M[2][3] = 1,x,2,y,3,z;
500   product(M);
501   intvec v=2,4,6;
502   product(M,v);
503   intvec iv = 1,2,3,4,5,6,7,8,9;
504   v=1..5,7,9;
505   product(iv,v);
506   intmat A[2][3] = 1,1,1,2,2,2;
507   product(A,3..5);
508}
509///////////////////////////////////////////////////////////////////////////////
510
511proc ringweights (r)
512"USAGE:   ringweights(r); r ring
513RETURN:  intvec of weights of ring variables. If, say, x(1),...,x(n) are the
514         variables of the ring r, in this order, the resulting intvec is
515         deg(x(1)),...,deg(x(n)) where deg denotes the weighted degree if
516         the monomial ordering of r has only one block of type ws,Ws,wp or Wp.
517NOTE:    In all other cases, in particular if there is more than one block,
518         the resulting intvec is 1,...,1
519EXAMPLE: example ringweights; shows an example
520"
521{
522   int i; intvec v; setring r;
523   for (i=1; i<=nvars(basering); i=i+1) { v[i] = deg(var(i)); }
524   return(v);
525}
526example
527{ "EXAMPLE:"; echo = 2;
528   ring r1=32003,(x,y,z),wp(1,2,3);
529   ring r2=32003,(x,y,z),Ws(1,2,3);
530   ring r=0,(x,y,u,v),lp;
531   intvec vr=ringweights(r1); vr;
532   ringweights(r2);
533   ringweights(r);
534}
535///////////////////////////////////////////////////////////////////////////////
536
537proc sort (id, list #)
538"USAGE:   sort(id[v,o,n]); id=ideal/module/intvec/list (of intvec's or int's)
539         sort may be called with 1, 2 or 3 arguments in the following way:
540         -  sort(id[v,n]); v=intvec of positive integers, n=integer,
541         -  sort(id[o,n]); o=string (any allowed ordstr of a ring), n=integer
542RETURN:  a list of two elements:
543         [1]: object of same type as input but sorted in the following manner:
544           - if id=ideal/module: generators of id are sorted w.r.t. intvec v
545             (id[v[1]] becomes 1-st, id[v[2]]  2-nd element, etc.). If no v is
546             present, id is sorted w.r.t. ordering o (if o is given) or w.r.t.
547             actual monomial ordering (if no o is given):
548                    generators with smaller leading term come first
549             (e.g. sort(id); sorts w.r.t actual monomial ordering)
550           - if id=list of intvec's or int's: consider a list element, say
551             id[1]=3,2,5, as exponent vector of the monomial x^3*y^2*z^5;
552             the corresponding monomials are ordered w.r.t. intvec v (s.a.).
553             If no v is present, the monomials are sorted w.r.t. ordering o
554             (if o is given) or w.r.t. lexicographical ordering (if no o is
555             given). The corresponding ordered list of exponent vectors is
556             returned.
557             (e.g. sort(id); sorts lexicographically, smaller int's come first)
558             WARNING: Since negative exponents create the 0 polynomial in
559             Singular, id should not contain negative integers: the result
560             might not be as expected
561           - if id=intvec: id is treated as list of integers
562           - if n!=0 the ordering is inverse, i.e. w.r.t. v(size(v)..1)
563             default: n=0
564         [2]: intvec, describing the permutation of the input (hence [2]=v if
565             v is given (with positive integers)
566NOTE:    If v is given id may be any simply indexed object (e.g. any list or
567         string); if v[i]<0 and i<=size(id) v[i] is set internally to i;
568         entries of v must be pairwise distinct to get a permutation if id.
569         Zero generators of ideal/module are deleted
570EXAMPLE: example sort; shows an example
571"
572{
573   int ii,jj,s,n = 0,0,1,0;
574   intvec v;
575   if ( defined(basering) ) { def P = basering; }
576   if ( size(#)==0 and (typeof(id)=="ideal" or typeof(id)=="module") )
577   {
578      id = simplify(id,2);
579      for ( ii=1; ii<size(id); ii++ )
580      {
581         if ( id[ii]!=id[ii+1] ) { break;}
582      }
583      if ( ii != size(id) ) { v = sortvec(id); }
584      else  { v = size(id)..1; }
585   }
586   if ( size(#)>=1 and (typeof(id)=="ideal" or typeof(id)=="module") )
587   {
588      if ( typeof(#[1])=="string" )
589      {
590         execute "ring r1 =("+charstr(P)+"),("+varstr(P)+"),("+#[1]+");";
591         def i = imap(P,id);
592         v = sortvec(i);
593         setring P;
594         n=2;
595      }
596   }
597   if ( typeof(id)=="intvec" or typeof(id)=="list" and n==0 )
598   {
599      string o;
600      if ( size(#)==0 ) { o = "lp"; n=1; }
601      if ( size(#)>=1 )
602      {
603         if ( typeof(#[1])=="string" ) { o = #[1]; n=1; }
604      }
605   }
606   if ( typeof(id)=="intvec" or typeof(id)=="list" and n==1 )
607   {
608      if ( typeof(id)=="list" )
609      {
610         for (ii=1; ii<=size(id); ii++)
611         {
612            if (typeof(id[ii]) != "intvec" and typeof(id[ii]) != "int")
613               { "// list elements must be intvec/int"; return(); }
614            else
615               { s=size(id[ii])*(s < size(id[ii])) + s*(s >= size(id[ii])); }
616         }
617      }
618      execute "ring r=0,x(1..s),("+o+");";
619      ideal i;
620      poly f;
621      for (ii=1; ii<=size(id); ii++)
622      {
623         f=1;
624         for (jj=1; jj<=size(id[ii]); jj++)
625         {
626            f=f*x(jj)^(id[ii])[jj];
627         }
628         i[ii]=f;
629      }
630      v = sort(i)[2];
631   }
632   if ( size(#)!=0 and n==0 ) { v = #[1]; }
633   if( size(#)==2 )
634   {
635      if ( #[2] != 0 ) { v = v[size(v)..1]; }
636   }
637   s = size(v);
638   if( size(id) < s ) { s = size(id); }
639   def m = id;
640   if ( size(m) != 0 )
641   {
642      for ( jj=1; jj<=s; jj=jj+1)
643      {
644         if ( v[jj]<=0 ) { v[jj]=jj; }
645         m[jj] = id[v[jj]];
646      }
647   }
648   if ( v == 0 ) { v = 1; }
649   list L=m,v;
650   return(L);
651}
652example
653{  "EXAMPLE:"; echo = 2;
654   ring r0 = 0,(x,y,z),lp;
655   ideal i = x3,y3,z3,x2z,x2y,y2z,y2x,z2y,z2x,xyz;
656   show(sort(i));"";
657   show(sort(i,"wp(1,2,3)"));"";
658   intvec v=10..1;
659   show(sort(i,v));"";
660   show(sort(i,v,1));"";   // should be the identity
661   ring r1  = 0,t,ls;
662   ideal j = t14,t6,t28,t20,t12,t34,t26,t18,t40,t32,t24,t38,t30,t36;
663   show(sort(j)[1]);"";
664   show(sort(j,"lp")[1]);"";
665   list L =1,5..8,10,2,8..5,8,3..10;
666   sort(L)[1];"";          // sort L lexicographically
667   sort(L,"Dp",1)[1];      // sort L w.r.t (total sum, reverse lex)
668}
669///////////////////////////////////////////////////////////////////////////////
670
671proc sum (id, list #)
672"USAGE:    sum(id[,v]); id=ideal/vector/module/matrix resp. id=intvec/intmat,
673                       v=intvec (e.g. v=1..n, n=integer)
674RETURN:   poly resp. int which is the sum of all entries of id, with index
675          given by v (default: v=1..number of entries of id)
676NOTE:     id is treated as a list of polys resp. integers. A module m is
677          identified with corresponding matrix M (columns of M generate m)
678EXAMPLE:  example sum; shows an example
679"
680{
681   if( typeof(id)=="poly" or typeof(id)=="ideal" or typeof(id)=="vector"
682       or typeof(id)=="module" or typeof(id)=="matrix" )
683   {
684      ideal i = ideal(matrix(id));
685      if( size(#)!=0 ) { i = i[#[1]]; }
686      matrix Z = matrix(i);
687   }
688   if( typeof(id)=="int" or typeof(id)=="intvec" or typeof(id)=="intmat" )
689   {
690      if ( typeof(id) == "int" ) { intmat S =id; }
691      else { intmat S = intmat(id); }
692      intvec i = S[1..nrows(S),1..ncols(S)];
693      if( size(#)!=0 ) { i = i[#[1]]; }
694      intmat Z=transpose(i);
695   }
696   intvec v; v[ncols(Z)]=0; v=v+1;
697   return((Z*v)[1,1]);
698}
699example
700{  "EXAMPLE:"; echo = 2;
701   ring r= 0,(x,y,z),dp;
702   vector pv = [xy,xz,yz,x2,y2,z2];
703   sum(pv);
704   //sum(pv,2..5);
705   //matrix M[2][3] = 1,x,2,y,3,z;
706   //sum(M);
707   //intvec w=2,4,6;
708   //sum(M,w);
709   //intvec iv = 1,2,3,4,5,6,7,8,9;
710   //w=1..5,7,9;
711   //sum(iv,w);
712   //intmat m[2][3] = 1,1,1,2,2,2;
713   //sum(m,3..4);
714}
715///////////////////////////////////////////////////////////////////////////////
716
717proc which (command)
718"USAGE:    which(command); command = string expression
719RETURN:   Absolute pathname of command, if found in search path.
720          Empty string, otherwise.
721NOTE:     Based on the Unix command 'which'.
722EXAMPLE:  example which; shows an example
723"
724{
725   int rs;
726   int i;
727   string fn = "/tmp/which_" + string(system("pid"));
728   string pn;
729   if( typeof(command) != "string")
730   {
731     return (pn);
732   }
733   i = system("sh", "which " + command + " > " + fn);
734   pn = read(fn);
735   pn[size(pn)] = "";
736   i = 1;
737   while ((pn[i] != " ") and (pn[i] != ""))
738   {
739     i = i+1;
740   }
741   if (pn[i] == " ") {pn[i] = "";}
742   rs = system("sh", "ls " + pn + " > " + fn + " 2>&1 ");
743   i = system("sh", "rm " + fn);
744   if (rs == 0) {return (pn);}
745   else
746   {
747     print (command + " not found ");
748     return ("");
749   }
750}
751example
752{  "EXAMPLE:"; echo = 2;
753    which("Singular");
754}
755///////////////////////////////////////////////////////////////////////////////
Note: See TracBrowser for help on using the repository browser.