source: git/Singular/LIB/purityfiltration.lib @ 33b509

spielwiese
Last change on this file since 33b509 was 1e1ec4, checked in by Oleksandr Motsak <motsak@…>, 11 years ago
Updated LIBs according to master add: new LIBs from master fix: updated LIBs due to minpoly/(de)numerator changes fix: -> $Id$ fix: Fixing wrong rebase of SW on master (LIBs)
  • Property mode set to 100644
File size: 24.1 KB
Line 
1/////////////////////////////////////////////////////////////////////////////
2//procedures examples comments
3version="$Id$";
4category="Noncommutative";
5info="
6LIBRARY: purityfiltration.lib     Algorithms for computing a purity filtration of a given module
7
8AUTHORS: Christian Schilli,        christian.schilli@rwth-aachen.de
9@*          Viktor Levandovskyy,   levandov@math.rwth-aachen.de
10
11
12OVERVIEW:
13Purity is a notion with several meanings. In our context it is equidimensionality
14@* of a module (that is all M is pure iff any nonzero submodule of N has the same dimension as N).
15@* Notably, one should define purity with respect to a given dimension function. In the context
16@* of this library the corresponding function is the homological grade number j_A(M) of a module M over
17@* an K-algebra A. j_A(M) is the minimal integer k, such that Ext^k_A(M,A) != 0.
18
19REFERENCES: [AQ] Alban Quadrat: Grade filtration of linear functional systems, INRIA Report 7769 (2010), to appear in Acta Applicanda Mathematica.
20@* [B93] Jan-Erik Bjoerk: Analytic D-modules and applications, Kluwer Acad. Publ., 1993.
21@* [MB10] Mohamed Barakat: Purity Filtration and the Fine Structure of Autonomy. Proc. MTNS, 2010.
22
23PROCEDURES:
24projectiveDimension(matrix T,int i);        compute a shortest resolution of coker(T) and its projective dimension
25purityFiltration(matrix R);                    compute the purity filtration of coker(R)
26purityTriang(matrix R)                        compute a triangular blockmatrix T, such that coker(R) isomorphic to coker(T)
27gradeNumber(matrix R);                              gives the grade number of the module coker(R)
28showgrades(list T);                           gives all grade numbers of the modules represented by the elements of T
29allExtOfLeft(matrix R);                              computes all right ext-modules ext^i(M,D) of a left module M=coker(R) over the ring D
30allExtOfRight(matrix R);                      computes all left ext-modules ext^i(M,D) of a right module M=coker(R) over the ring D
31doubleExt(matrix R, int i);                 computes the left module ext^i(ext^i(M,D),D) over the ring D, M=coker(R)
32allDoubleExt(matrix R);                              computes all double ext modules ext^i(ext^j(M,D),D) of the left module coker(R) over the ring D
33is_pure(matrix R);                              checks whether the module coker(R) is pure
34purelist(list T);                              checks whether all the modules represented by the elements of T are pure
35
36KEYWORDS: D-module; ext-module; filtration; projective dimension; resolution; purity
37";
38
39LIB "nctools.lib";
40LIB "matrix.lib";
41LIB "poly.lib";
42LIB "general.lib";
43LIB "control.lib";
44LIB "nchomolog.lib";
45
46//------------------- auxiliary procedures --------------------------
47
48proc testPurityfiltrationLib()
49{
50example projectiveDimension;
51example purityFiltration;
52example purityTriang;
53example gradeNumber;
54example showgrades;
55example allExtOfLeft;
56example allExtOfRight;
57example doubleExt;
58example allDoubleExt;
59example is_pure;
60example purelist;
61}
62
63static proc iszero (matrix R)
64"USAGE:  iszero(R); R a matrix
65RETURN:  int, 1, if R is zero,
66@*              or 0, if it's not
67PURPOSE: checks, if the matrix R is zero or not
68"
69{
70  ideal i=R;
71  i=std(i);
72  if (i==0)
73  {
74    return (1);
75  }
76  return (0);
77}
78
79proc lsyz (matrix R)
80"USAGE:  lsyz(R), R a matrix
81RETURN:         matrix, a left syzygy of R
82PURPOSE: computes the left syzygy module of the module, generated by the rows of R, i.e.
83@*         a matrix X with X*R=0
84"
85{
86  matrix L=transpose(syz(transpose(R)));
87  return(L);
88}
89
90proc rsyz (matrix R)
91"USAGE:  rsyz(R), R a matrix
92RETURN:         matrix, a rightsyzygy of R
93PURPOSE: computes the right syzygy module of the module, generated by the rows of R, i.e.
94@*         a matrix X with R*X=0
95EXAMPLE: example rsyz; shows example
96"
97{
98  def save = basering;            // with respect to non-commutative rings,
99  def saveop = opposite(save);    // we have to switch to the oppose ring for a rightsyzygy
100  setring saveop;
101  matrix Rop = oppose(save,R);
102  matrix Bop = syz(Rop);
103  setring save;
104  matrix B =oppose(saveop,Bop);
105  kill saveop;
106  return(B);
107}
108example
109{"EXAMPLE:";echo = 2;
110  ring D = 0,(x,y,z),dp;
111  matrix R[3][2]=x,0,0,x,y,-z;
112  matrix X=rsyz(R);
113  print(X);
114  // check
115  print(R*X);
116}
117
118
119static proc rinv (matrix R)
120"USAGE:  rinv(R), R a matrix
121RETURN:         matrix, a right inverse of R
122PURPOSE: computes a right inverse matrix of R, if it exists
123@*         if not, it returns the zero matrix
124"
125{
126  return(rightInverse(R));
127}
128
129static proc linv (matrix R)
130"USAGE:  linv(R), R a matrix
131RETURN:         matrix, a left inverse of R
132PURPOSE: computes a left inverse matrix of R, if it exists
133@*         if not, it returns the zero matrix
134"
135{
136  return (leftInverse(R));
137}
138
139proc rlift(matrix M, matrix N)
140"USAGE:  rlift(M,N), M and N matrices, so that the module, generated by the columns of N
141@*         is a submodule of the one, generated by the columns of M
142RETURN:         matrix, a right lift of N in M
143PURPOSE: computes a right lift matrix X of N in M,
144@*         i.e. N=M*X
145"
146{
147  def save = basering;           // with respect to non-commutative rings,
148  def saveop = opposite(save);   // we have to change the ring for a rightlift
149  setring saveop;
150  matrix Mop = oppose(save,M);
151  matrix Nop = oppose(save,N);
152  matrix Bop = lift(Mop,Nop);
153  setring save;
154  matrix B =oppose(saveop,Bop);
155  kill saveop;
156  return(B);
157}
158
159proc llift(matrix M, matrix N)
160"USAGE:  llift(M,N), M and N matrices, so that the module, generated by the rows of N
161@*         is a submodule of the one, generated by the rows of M
162RETURN:         matrix, a left lift of N in M
163PURPOSE: computes a left lift matrix X of N in M,
164@*         i.e. N=X*M
165"
166{
167  matrix X=transpose(lift(transpose(M),transpose(N)));
168  return(X);
169}
170
171static proc concatz(matrix M, matrix N)
172"USAGE:  concatz(M,N), M and N matrices
173RETURN:         matrix
174PURPOSE: adds the rows of N under the rows of M, i.e. build the matrix (M^Tr,N^Tr)^Tr
175"
176{
177  matrix X=transpose(concat(transpose(M),transpose(N)));
178  return (X);
179}
180
181//------------------------- main procedures --------------------------
182
183proc purityFiltration(matrix R)
184"USAGE:  purityFiltration(S), S matrix with entries of an Auslander regular ring D
185RETURN:         a list T of two lists, purity filtration of the module M=D^q/D^p(S^t)
186PURPOSE: the first list T[1] gives a filtration {M_i} of M,
187@*         where the i-th entry of T[1] gives the representation matrix of M_(i-1).
188@*         the second list T[2] gives representations of the factor Modules,
189@*         i.e. T[2][i] gives the repr. matrix for M_(i-1)/M_i
190EXAMPLE: example purityFiltration; shows example
191"
192{
193  int i,j;
194  list re=projectiveDimension(R,0);
195  list T=re[1];
196  int di=re[2];
197  list reres;             // Rji=reres[i][j+1], i=1,..,n+1; j=0,..,i
198  for( i=1; i<=di+1; i++ )
199  {
200    list zw;
201    zw[i+1]=T[i];
202    for( j=i; j >= 1; j--)
203    {
204      zw[j]=rsyz(zw[j+1]);
205    }
206    reres[i]=zw;
207    kill zw;
208  }
209  list F;    // Fij=F[j][i+1], j=2,..,n+1; i=0,..,j-1
210  for(i=2;i<=di;i++)
211  {
212    list ehm;
213    matrix I[nrows(T[i-1])][nrows(T[i-1])];
214    I=I+1;
215    ehm[i]=I;
216    kill I;
217    for (j=1; j<=i-1; j++)
218    {
219      ehm[i-j]=rlift(reres[i][i-j+1],ehm[i-j+1]*reres[i-1][i-j+1]);
220    }
221    F[i]=ehm;
222    kill ehm;
223  }
224//  list M;       // Mi=M[i+1], i=0,...,n+1
225//  M[1]=R1;
226//  matrix Ti=lsyz(reres[1][1]);
227//  matrix P[ncols(Ti)][ncols(Ti)];
228//  P=P+1;
229//  for (i=1;i<=di; i++)
230//  {
231//    M[i+1]=transpose(modulo(transpose(Ti*P),transpose(reres[i][2])));
232//    P=F[i+1][1]*P;
233//    Ti=lsyz(reres[i+1][1]);
234//  }
235//  M[di+2]=transpose(modulo(transpose(Ti*P),transpose(reres[di+1][2])));
236//  list I;
237//  for (i=1;i<=di+1;i++)
238//  {
239//    I[i]=transpose(modulo(transpose(M[i]),transpose(M[i+1])));
240//  }
241  list Rs,Rss;
242  for(i=1; i<=di; i++)
243  {
244    list zw;
245    zw[1]=lsyz(reres[i][1]);
246    zw[2]=lsyz(zw[1]);
247    Rss[i]=llift(zw[1],reres[i][2]);
248    Rs[i]=zw;
249    kill zw;
250  }
251  list Fs;
252  for(i=2;i<=di;i++)
253  {
254    Fs[i]=llift(Rs[i-1][1],Rs[i][1]*F[i][1]);
255  }
256  list K,U;
257  K[1]=transpose(R);
258  U[1]=Rs[1][1];
259  for(i=2;i<=di;i++)
260  {
261    K[i]=transpose(std(transpose(concatz(Rss[i-1], Rs[i-1][2]))));
262    U[i]=transpose(std(transpose(concatz(concatz(Fs[i],Rss[i-1]),Rs[i-1][2]))));
263  }
264  K[di+1]=transpose(std(transpose(concatz(Rss[di], Rs[di][2]))));
265  U[di+1]=K[di+1];
266  list erg=(K,U);
267  return (erg);
268}
269example
270{"EXAMPLE:";echo = 2;
271  ring D = 0,(x1,x2,d1,d2),dp;
272  def S=Weyl();
273  setring S;
274  int i;
275  matrix R[3][3]=0,d2-d1,d2-d1,d2,-d1,-d1-d2,d1,-d1,-2*d1;
276  print(R);
277  list T=purityFiltration(transpose(R));
278  // the purity filtration of coker(M)
279  print(T[1][1]);
280  print(T[1][2]);
281  print(T[1][3]);
282  // factor modules of the filtration
283  print(T[2][1]);
284  print(T[2][2]);
285  print(T[2][3]);
286}
287
288
289proc purityTriang(matrix R)
290"USAGE:  purityTriang(S), S matrix with entries of an Auslander regular ring D
291RETURN:         a matrix T
292PURPOSE: compute a triangular block matrix T, such that M=D^p/D^q(S^t) is isomorphic to M'=D^p'/D^q(T^t)
293EXAMPLE: example purityTriang; shows example
294"
295{
296  int i,j;
297  list re=projectiveDimension(R,0);
298  list T=re[1];
299  int di=re[2];
300  list reres;             // Rji=reres[i][j+1], i=1,..,n+1; j=0,..,i
301  for( i=1; i<=di+1; i++ )
302  {
303    list zw;
304    zw[i+1]=T[i];
305    for( j=i; j >= 1; j--)
306    {
307      zw[j]=rsyz(zw[j+1]);
308    }
309    reres[i]=zw;
310    kill zw;
311  }
312  list F;    // Fij=F[j][i+1], j=2,..,n+1; i=0,..,j-1
313  for(i=2;i<=di;i++)
314  {
315    list ehm;
316    matrix I[nrows(T[i-1])][nrows(T[i-1])];
317    I=I+1;
318    ehm[i]=I;
319    kill I;
320    for (j=1; j<=i-1; j++)
321    {
322      ehm[i-j]=rlift(reres[i][i-j+1],ehm[i-j+1]*reres[i-1][i-j+1]);
323    }
324    F[i]=ehm;
325    kill ehm;
326  }
327
328  list Rs,Rss;
329  for(i=1; i<=di; i++)
330  {
331    list zw;
332    zw[1]=lsyz(reres[i][1]);
333    zw[2]=lsyz(zw[1]);
334    Rss[i]=llift(zw[1],reres[i][2]);
335    Rs[i]=zw;
336    kill zw;
337  }
338  list Fs;
339  for(i=2;i<=di;i++)
340  {
341    Fs[i]=llift(Rs[i-1][1],Rs[i][1]*F[i][1]);
342  }
343
344
345  int sp; list spnr;
346  spnr[1]=ncols(Rs[1][1]);
347  for (i=2;i<=di;i++)
348    {
349      spnr[i]=ncols(Fs[i]);
350    }
351  spnr[di+1]=ncols(Rss[di]);
352  sp=sum(spnr);
353
354  matrix E[nrows(Rs[1][1])][nrows(Rs[1][1])]; E=E-1;
355  list Z; int sumh;
356  Z[1]=concat(Rs[1][1],E);
357  sumh=ncols(Rs[1][1]);
358  kill E;
359
360  for(i=2;i<=di;i++)
361  {
362    matrix A;
363    matrix B[1][sumh];
364    matrix E[nrows(Fs[i])][nrows(Fs[i])]; E=E-1;
365
366    A=Fs[i];
367    if (i>2)
368    {
369      if (iszero(Rss[i-1])==0)
370      {
371        A=concatz(A,Rss[i-1]);
372      }
373    }
374    if (iszero(Rs[i-1][2])==0)
375    {
376      A=concatz(A,Rs[i-1][2]);
377    }
378    A=concat(B,A,E);
379    Z[i]=A;
380    sumh=sumh+spnr[i];
381    kill A,B,E;
382  }
383
384
385  matrix hi,his;
386  matrix N[1][sumh];
387
388  if (iszero(Rss[di])==0)
389  {
390    hi=concat(N,Rss[di]);
391  }
392
393  if (iszero(Rs[di][2])==0)
394  {
395    his=concat(N,Rs[di][2]);
396    if (iszero(hi)==1)
397    {
398      hi=his;
399    }
400    if (iszero(hi)==0)
401    {
402    hi=concatz(hi,his);
403    }
404  }
405
406  kill his;
407
408  matrix ges=Z[1];
409  for (i=2;i<=di;i++)
410  {
411    ges = concatz(ges,Z[i]);
412  }
413
414  if (iszero(hi)==0)
415  {
416    ges=concatz(ges,hi);
417  }
418return (ges);
419}
420example
421{"EXAMPLE:";echo = 2;
422  ring D = 0,(x1,x2,d1,d2),dp;
423  def S=Weyl();
424  setring S;
425  int i;
426  matrix R[3][3]=0,d2-d1,d2-d1,d2,-d1,-d1-d2,d1,-d1,-2*d1;
427  print(R);
428  matrix T=purityTriang(transpose(R));
429  // a triangular blockmatrix representing the module coker(R)
430  print(T);
431}
432
433
434proc gradeNumber(matrix R)
435"USAGE:  gradeNumber(R), R matrix, representing M=D^p/D^q(R^t) over a ring D
436RETURN:         int, grade number of M
437PURPOSE: computes the grade number of M, i.e. the first i, with ext^i(M,D) !=0
438@*         returns -1 if M=0
439EXAMPLE: example gradeNumber; shows examples
440"
441{
442  matrix M=transpose(R);
443  if (is_zero(transpose(M))==1)
444  {
445    return (-1);
446  }
447  list ext = allExtOfLeft(transpose(M));
448  int i=1;
449  matrix L=ext[i];
450  while (is_zero(transpose(L))==1)
451  {
452    i=i+1;
453    L=ext[i];
454  }
455  return (i-1);
456}
457example
458{"EXAMPLE:";echo = 2;
459  // trivial example
460  ring D=0,(x,y,z),dp;
461  matrix R[2][1]=1,x;
462  gradeNumber(R);
463  // R has left inverse, so M=D/D^2R=0
464  gradeNumber(transpose(R));
465  print(ncExt_R(0,R));
466  // so, ext^0(coker(R),D) =! 0)
467  //
468  // a little bit more complex
469  matrix R1[3][1]=x,-y,z;
470  gradeNumber(transpose(R1));
471  print(ncExt_R(0,transpose(R1)));
472  print(ncExt_R(1,transpose(R1)));
473  print(ncExt_R(2,transpose(R1)));
474  // ext^i are zero for i=0,1,2
475  matrix ext3=ncExt_R(3,transpose(R1));
476  print(ext3);
477  // not zero
478  is_zero(ext3);
479}
480
481proc allExtOfLeft(matrix Ps)
482"USAGE:  allExtOfLeft(M),
483RETURN:         list, entries are ext-modules
484ASSUME: M presents a left module of finite left projective dimension n
485PURPOSE: For a left module presented by M over the basering D,
486@*           compute a list T, whose entry T[i+1] is a matrix, presenting the right module Ext^i_D(M,D) for i=0..n
487EXAMPLE: example allExtOfLeft; shows example
488"
489{
490  // old doc: ... T[i] gives the repr. matrix of ext^(i-1)(M,D), i=1,.., n+1
491  list ext, Phi;
492  ext[1]=ncHom_R(Ps);
493  Phi = mres(Ps,0);
494  int di = size(Phi);
495  Phi[di+1]= transpose(lsyz(transpose(Phi[di])));
496  int i;
497  def Rbase = basering;
498  for(i=1;i<=di;i++)
499  {
500    module f   = transpose(matrix(Phi[i+1]));
501    module Im2 = transpose(matrix(Phi[i]));
502    def Rop   = opposite(Rbase);
503    setring Rop;
504    module fop    = oppose(Rbase,f);
505    module Im2op  = oppose(Rbase,Im2);
506    module ker_op = modulo(fop,std(0));
507    module ext_op = modulo(ker_op,Im2op);
508    setring Rbase;
509    ext[i+1] = oppose(Rop,ext_op); // a right module!
510    kill f, Im2, Rop;
511  }
512  return(ext);
513}
514example
515{"EXAMPLE:";echo = 2;
516  ring D = 0,(x,y,z),dp;
517  matrix R[6][4]=
518  0,-2*x,z-2*y-x,-1,
519  0,z-2*x,2*y-3*x,1,
520  z,-6*x,-2*y-5*x,-1,
521  0,y-x,y-x,0,
522  y,-x,-y-x,0,
523  x,-x,-2*x,0;
524  // coker(R) consider the left module M=D^6/D^4R
525  list T=allExtOfLeft(transpose(R));
526  print(T[1]);
527  print(T[2]);
528  print(T[3]);
529  print(T[4]);
530  // right modules coker(T[i].)!!
531}
532
533proc allExtOfRight(matrix Ps)
534"USAGE:  allExtOfRight(R), R matrix representing the right Module M=D^q/RD^p over a ring D
535@*           M module with finite right projective dimension n
536RETURN:         list, entries are ext-modules
537PURPOSE: computes a list T, which entries are representations of the left modules ext^i(M,D)
538@*         T[i] gives the repr. matrix of ext^(i-1)(M,D), i=1,..,n+1
539EXAMPLE: example allExtOfRight; shows example
540"
541{
542  // matrix Ps=transpose(Y);
543  list ext, Phi;
544  def Rbase = basering;
545  def Rop   = opposite(Rbase);
546  setring Rop;
547  matrix Psop=oppose(Rbase,Ps);
548  matrix ext1_op = ncHom_R(Psop);
549  setring Rbase;
550  ext[1]=oppose(Rop,ext1_op);
551  kill Rop;
552  list zw = rightreso(transpose(Ps)); // right resolution
553  int di = size(zw);
554  zw[di+1]=lsyz(zw[di]);
555  Phi = zw;
556  kill zw;
557  int i;
558  for(i=1;i<=di;i++)
559  {
560    module f   = Phi[i+1];
561    module Im2 = Phi[i];
562    module ker = modulo(f,std(0));
563    ext[i+1] = modulo(ker,Im2);  // a left module!
564    kill f, Im2, ker;
565  }
566  return(ext);
567}
568example
569{"EXAMPLE:";echo = 2;
570  ring D = 0,(x,y,z),dp;
571  matrix R[6][4]=
572  0,-2*x,z-2*y-x,-1,
573  0,z-2*x,2*y-3*x,1,
574  z,-6*x,-2*y-5*x,-1,
575  0,y-x,y-x,0,
576  y,-x,-y-x,0,
577  x,-x,-2*x,0;
578  // coker(R) considered as right module
579  projectiveDimension(R,1)[2];
580  list T=allExtOfRight(R);
581  print(T[1]);
582  print(T[2]);
583  // left modules coker(.T[i])!!
584}
585
586static proc rightreso(matrix T)
587"USAGE:  rightreso(T), T matrix representing the right module M=D*/TD*
588RETURN:         list L, a right resolution of M
589PURPOSE: computes a right resolution of M, using mres
590@*         the i-th entry of L gives the (i-1)th right syzygy module of M
591"
592{
593  int j;
594  matrix M=transpose(T);
595  list res;
596  def save = basering;            // with respect to non-commutative rings,
597  def saveop = opposite(save);    // we have to change the ring for a rightresolution
598  setring saveop;
599  matrix Mop=oppose(save,M);
600  list aufl=mres(Mop,0);
601  list resop=aufl;
602  kill aufl;
603  for (j=1; j<=size(resop); j++)
604  {
605    matrix zw=resop[j];
606    setring save;
607    res[j]=transpose(oppose(saveop,zw));
608    setring saveop;
609    kill zw;
610  }
611  setring save;
612  kill saveop;
613  return(res);
614}
615
616proc showgrades(list T)
617"USAGE:  showgrades(T), T list, which includes representation matrices of modules
618RETURN:         list, gradenumbers of the entries in T
619PURPOSE: computes a list L with L[i]=gradenumber(M), M=D^p/D^qT[i]
620EXAMPLE: example showgrades; shows example
621"
622{
623  list grades;
624  int gr=size(T);
625  int i;
626  for (i=1;i<=gr;i++)
627  {
628    grades[i]=gradeNumber(transpose(T[i]));
629  }
630  return (grades);
631}
632example
633{"EXAMPLE:";echo = 2;
634  ring D = 0,(x,y,z),dp;
635  matrix R[6][4]=
636  0,-2*x,z-2*y-x,-1,
637  0,z-2*x,2*y-3*x,1,
638  z,-6*x,-2*y-5*x,-1,
639  0,y-x,y-x,0,
640  y,-x,-y-x,0,
641  x,-x,-2*x,0;
642  list T=purityFiltration(transpose(R))[2];
643  showgrades(T);
644  // T[i] are i-1 pure (i=1,3,4) or zero (i=2)
645}
646
647proc doubleExt(matrix R, int i)
648"USAGE:  doubleExt(R,i), R matrix representing the left Module M=D^p/D^q(R^t) over a ring D
649@*         int i, less or equal the left projective dimension of M
650RETURN:         matrix P, representing the double ext module
651PURPOSE: computes a matrix P, which represents the left module ext^i(ext^i(M,D))
652EXAMPLE: example doubleExt; shows example
653"
654{
655  return (allExtOfRight(   allExtOfLeft(R)[i+1]   )[i+1]);
656}
657example
658{"EXAMPLE:";echo = 2;
659  ring D = 0,(x,y,z),dp;
660  matrix R[7][3]=
661  0 ,0,1,
662  1 ,-4*x+z,-z,
663  -1,8*x-2*z,z,
664  1 ,0  ,0,
665  0 ,x-y,0,
666  0 ,x-y,y,
667  0 ,0  ,x;
668  // coker(R) is 2-pure, so all doubleExt are zero
669  print(doubleExt(transpose(R),0));
670  print(doubleExt(transpose(R),1));
671  print(doubleExt(transpose(R),3));
672  // except of the second
673  print(doubleExt(transpose(R),2));
674}
675
676proc allDoubleExt(matrix R)
677"USAGE:  allDoubleExt(R), R matrix representing the left Module M=D^p/D^q(R^t) over a ring D
678RETURN:         list T, double indexed, which include all double-ext modules
679PURPOSE: computes all double ext-modules
680@*         T[i][j] gives a representation matrix of ext^(j-1)(ext(i-1)(M,D))
681EXAMPLE: example allDoubleExt; shows example
682"
683{
684list ext=allExtOfLeft(transpose(R));
685list extext;
686int i;
687for(i=1;i<=size(ext);i++)
688  {
689    extext[i]=allExtOfRight(ext[i]);
690  }
691kill ext;
692return (extext);
693}
694example
695{"EXAMPLE:";echo = 2;
696  ring D = 0,(x1,x2,x3,d1,d2,d3),dp;
697  def S=Weyl();
698  setring S;
699  matrix R[6][4]=
700  0,-2*d1,d3-2*d2-d1,-1,
701  0,d3-2*d1,2*d2-3*d1,1,
702  d3,-6*d1,-2*d2-5*d1,-1,
703  0,d2-d1,d2-d1,0,
704  d2,-d1,-d2-d1,0,
705  d1,-d1,-2*d1,0;
706  list T=allDoubleExt(transpose(R));
707  // left projective dimension of M=coker(R) is 3
708  // ext^i(ext^0(M,D)), i=0,1,2,3
709  print(T[1][1]);
710  print(T[1][2]);
711  print(T[1][3]);
712  print(T[1][4]);
713  // ext^i(ext^1(M,D)), i=0,1,2,3
714  print(T[2][1]);
715  print(T[2][2]);
716  print(T[2][3]);
717  print(T[2][4]);
718  // ext^i(ext^2(M,D)), i=0,1,2,3  (all zero)
719  print(T[3][1]);
720  print(T[3][2]);
721  print(T[3][3]);
722  print(T[3][4]);
723  // ext^i(ext^3(M,D)), i=0,1,2,3  (all zero)
724  print(T[4][1]);
725  print(T[4][2]);
726  print(T[4][3]);
727  print(T[4][4]);
728}
729
730proc is_pure(matrix R)
731"USAGE:  is_pure(R), R representing the module M=D^p/D^q(R^t)
732RETURN:         int, 0 or 1
733PURPOSE: checks pureness of M.
734@*         returns 1, if M is pure, or 0, if it's not
735@*         remark: if M is zero, is_pure returns 1
736EXAMPLE: example is_pure; shows example
737"
738{
739  matrix M=transpose(R);
740  int gr=gradeNumber(transpose(M));
741  int di=projectiveDimension(transpose(M),0)[2];
742  int i=0;
743  while(i<=di)
744  {
745    if (i!=gr)
746    {
747      if (  is_zero( doubleExt(transpose(M),i) ) == 0 )
748      {
749        return (0);
750      }
751    }
752    i=i+1;
753  }
754  return (1);
755}
756example
757{"EXAMPLE:";echo = 2;
758  ring D = 0,(x,y,z),dp;
759  matrix R[3][2]=y,-z,x,0,0,x;
760  list T=purityFiltration(transpose(R));
761  print(transpose(std(transpose(T[2][2]))));
762  // so the purity filtration of coker(R) is trivial,
763  // i.e. coker(R) is already pure
764  is_pure(transpose(R));
765  // we can also have non-pure modules:
766  matrix R2[6][4]=
767  0,-2*x,z-2*y-x,-1,
768  0,z-2*x,2*y-3*x,1,
769  z,-6*x,-2*y-5*x,-1,
770  0,y-x,y-x,0,
771  y,-x,-y-x,0,
772  x,-x,-2*x,0;
773  is_pure(transpose(R2));
774}
775
776proc purelist(list T)
777"USAGE:  purelist(T), T list, in which the i-th entry R=T[i] represents M=D^p/D^q(R^t)
778RETURN:         list M, entries of M are 0 or 1
779PURPOSE: if T[i] is pure, M[i] is 1, else M[i] is 0
780EXAMPLE: example purelist; shows example
781"
782{
783  int i;
784  list erg;
785  for(i=1;i<=size(T);i++)
786  {
787    erg[i]=is_pure(transpose(T[i]));
788  }
789  return (erg);
790}
791example
792{"EXAMPLE:";echo = 2;
793  ring D = 0,(x,y,z),dp;
794  matrix R[6][4]=
795  0,-2*x,z-2*y-x,-1,
796  0,z-2*x,2*y-3*x,1,
797  z,-6*x,-2*y-5*x,-1,
798  0,y-x,y-x,0,
799  y,-x,-y-x,0,
800  x,-x,-2*x,0;
801  is_pure(transpose(R));
802  // R is not pure, so we do the purity filtration
803  list T=purityFiltration(transpose(R));
804  // all Elements of T[2] are either zero or pure
805  purelist(T[2]);
806}
807
808
809proc projectiveDimension(matrix T, list #)
810"USAGE:  projectiveDimension(R,i,j), R matrix representing the Modul M=coker(R)
811@*       int i, with i=0 or i=1, j a natural number
812RETURN:  list T, a projective resolution of M and its projective dimension
813PURPOSE: if i=0 (and by default), T[1] gives a shortest left resolution of M=D^p/D^q(R^t) and T[2] the left projective dimension of M
814@*         if i=1, T[1] gives a shortest right resolution of M=D^p/RD^q and T[2] the right projective dimension of M
815@*          in both cases T[1][j] is the (j-1)-th syzygy module of M
816NOTE: The algorithm is due to A. Quadrat, D. Robertz, Computation of bases of free modules over the Weyl algebras, J.Symb.Comp. 42, 2007.
817EXAMPLE: example projectiveDimension; shows examples
818"
819{
820  int i = 0; // default
821  if (size(#) >0)
822  {
823    i = int(#[1]);
824    if ( (i!=0) and (i!=1) )
825    {
826      printf("Unaccepted second argument. Use 0 to get a left resolution, 1 for a right one.");
827    }
828  }
829  if (i==0)
830  {
831    return(prodim(T));
832  }
833    int j;
834    matrix M=T;
835    list res;
836    def save = basering;            // with respect to non-commutative rings,
837    def saveop = opposite(save);    // we have to change the ring for a rightresolution
838    setring saveop;
839    matrix Mop=oppose(save,M);
840    list aufl=prodim(Mop);
841    int k=aufl[2];
842    list resop=aufl[1];
843    kill aufl;
844    for (j=1; j<=size(resop); j++)
845    {
846      matrix zw=resop[j];
847      setring save;
848      res[j]=transpose(oppose(saveop,zw));
849      setring saveop;
850      kill zw;
851    }
852    setring save;
853    list Y;
854    Y[1]=res;
855    Y[2]=k;
856    kill saveop;
857    kill res;
858    return(Y);
859
860}
861example
862{"EXAMPLE:";echo = 2;
863  // commutative example
864  ring D = 0,(x,y,z),dp;
865  matrix R[6][4]=
866  0,-2*x,z-2*y-x,-1,
867  0,z-2*x,2*y-3*x,1,
868  z,-6*x,-2*y-5*x,-1,
869  0,y-x,y-x,0,
870  y,-x,-y-x,0,
871  x,-x,-2*x,0;
872  // compute a left resolution of M=D^4/D^6*R
873  list T=projectiveDimension(transpose(R),0);
874  // so we have the left projective dimension
875  T[2];
876  //we could also compute a right resolution of M=D^6/RD^4
877  list T1=projectiveDimension(R,1);
878  // and we have right projective dimension
879  T1[2];
880  // check, that a syzygy matrix of R has left inverse:
881  print(leftInverse(syz(R)));
882  // so lpd(M) must be 1.
883  // Non-commutative example
884  ring D1 = 0,(x1,x2,x3,d1,d2,d3),dp;
885  def S=Weyl();  setring S;
886  matrix R[3][3]=
887  1/2*x2*d1, x2*d2+1, x2*d3+1/2*d1,
888  -1/2*x2*d2-3/2,0,1/2*d2,
889  -d1-1/2*x2*d3,-d2,-1/2*d3;
890  list T=projectiveDimension(R,0);
891  // left projective dimension of coker(R) is
892  T[2];
893  list T1=projectiveDimension(R,1);
894  // both modules have the same projective dimension, but different resolutions, because D is non-commutative
895  print(T[1][1]);
896  // not the same as
897  print(transpose(T1[1][1]));
898}
899
900static proc prodim(matrix M)
901"USAGE:  prodim(R), R matrix representing the Modul M=coker(R)
902RETURN:  list T, a left projective resolution of M and its left projective dimension
903PURPOSE: T[1] gives a shortest left resolution of M and T[2] the left projective dimension of M
904@*         it is T[1][j] the (j-1)-th syzygy module of M
905"
906{
907  matrix T=transpose(M);
908  list R,zw;
909  R[1]=T;
910  if (rinv(R[1])==0)
911  {
912    R[2]=transpose(std(transpose(lsyz(R[1]))));
913  }
914  else
915  {
916    matrix S[1][ncols(T)];
917    R[1]=S;
918    zw[1]=R;
919    zw[2]=0;
920    return (zw);
921  }
922  if (iszero(R[2])==1)
923  {
924    zw[1]=R;
925    zw[2]=1;
926    return (zw);
927  }
928  int i=1;
929  matrix N;
930  while (iszero(R[i+1])==0)
931  {
932    i=i+1;
933    N=rinv(R[i]);
934    if (iszero(N)==0)
935    {
936      if (i==2)
937      {
938        R[i-1]=concat(R[i-1],N);
939        matrix K[1][nrows(R[1])];
940        R[2]=K;
941        zw[1]=R;
942        zw[2]=i-1;
943        return (zw);
944      }
945      if (i>2)
946      {
947        R[i-1]=concat(R[i-1],N);
948        matrix K[ncols(N)][1];
949        R[i-2]=concatz(R[i-2],K);
950        R[i]=0;
951        zw[1]=R;
952        zw[2]=i-1;
953        return(zw);
954      }
955    }
956    R[i+1]=transpose(std(transpose(lsyz(R[i]))));
957  }
958  zw[1]=R;
959  zw[2]=i;
960  return (zw);
961}
Note: See TracBrowser for help on using the repository browser.