source: git/Singular/LIB/tateProdCplxNegGrad.lib

spielwiese
Last change on this file was a7e3f75, checked in by Hans Schoenemann <hannes@…>, 3 years ago
fix: dup. truncate -> truncateM
  • Property mode set to 100644
File size: 63.0 KB
Line 
1///////////////////////////////////////////////////////////////////////////////
2// version ="version tateProdCplxNegGrad.lib 4.2.0.1 Dec_2020 "; //$id$
3info = "
4LIBRARY:   tateProdCplxNegGrad.lib for computing sheaf cohomology on product of projective spaces
5AUTHOR:   Clara Petroll (petroll@mathematik.uni-kl.de)
6OVERVIEW:  In this library, we use Tate resolutions for computing sheaf cohomology of coherent sheaves on products of projective spaces.
7      The algorithms can be used for arbitrary products. We work over the multigraded Cox ring and the corresponding exterior
8      algebra. Multigraded complexes are realized as the newstruct @code{multigradedcomplex}.
9
10      The main algorithm is the one for computing subquotient complexes of a Tate resolution. It allows to compute cohomologytables,
11      respectively hash table of the dimensions of sheaf cohomology groups.
12REFERENCES:  [1] Eisenbud, Erman, Schreyer: Tate Resolutions for Products of Projective Spaces, Acta Mathematica Vietnamica (2015)
13      [2] Eisenbud, Erman, Schreyer: Tate Resolutions on Products of Projective Spaces: Cohomology and Direct Image Complexes (2019)
14PROCEDURES:
15      productOfProjectiveSpaces(intvec c)                        creates rings S,E corresponding to the product
16      truncateM(module M, intvec c)                          truncates module M at c
17      truncateCoker(module M, intvec c)                        truncates the cokernel at c
18      symExt(matrix m)                                computes first differential of R(M)
19      sufficientlyPositiveMultidegree(module M)                    computes a sufficiently positive multidegree for M
20      tateResolution(module M, intvec low, intvec high)            computes subquotient complex of Tate resolution T(F)
21      cohomologyMatrix(module M, intvec low, intvec high)            computes cohomologymatrix of corresponding sheaf
22      cohomologyMatrixFromResolution(multigradedcomplex T, intvec low, intvec high)  computes dimensions of sheaf cohomology groups contained in T
23      eulerPolynomialTable(module M, intvec low, intvec high)          computes table of Euler polynomials
24      cohomologyHashTable(module M, intvec low, intvec high)          computes cohomology hash table
25      twist(module M,intvec c)                            twists module M by c
26      beilinsonWindow(multigradedcomplex T)                      computes Beilinson window of T
27      regionComplex(multigradedcomplex T, intvec d, intvec I, intvec J, intvec K)    computes region complex
28      strand(multigradedcomplex T, intvec c, intvec J)                computes strand
29      firstQuadrantComplex(multigradedcomplex T, intvec c)              computes first quadrant complex
30      lastQuadrantComplex(multigradedcomplex T, intvec c)                computes last quadrant complex
31      proc shift(multigradedcomplex A, int i)                      shifts the multigraded complex by i
32";
33
34
35///////////////////////////////////////////////////////////////////////////////
36//include necessary libraries
37LIB "multigrading.lib";
38LIB "matrix.lib";
39LIB "ring.lib";
40LIB "methods.lib";
41
42// Idee: in multigradedcomplex noch zusaetzlich ring E speichern
43static proc mod_init()
44{
45  newstruct("bundle","module m, int iscoker");
46  system("install","bundle","print",printBundle,1);
47  newstruct("multigradedcomplex","list differentials, list modules, int shift");
48  system("install","multigradedcomplex","print",printMultigradedComplex,1);
49}
50
51///////////////////////////////////////////////////////////////////////////////
52proc printMultigradedComplex(multigradedcomplex C)
53"USAGE:  printMultigradedComplex(C); C multigradedcomplex
54RETURN:  nothing, prints a multigraded complex
55EXAMPLE: example printMultigradedComplex
56"
57{
58  int sizeStringCplx, sizeStringDegrees, i,j;
59  string addedStringCplx, addedStringDegrees;
60
61  if (size(C.modules)==0)
62  {
63    print(0);
64  }
65  else
66  {
67    list exponents;
68    string cplx;
69    string degrees;
70    for (i = 1; i<= size(C.modules)-1; i++)
71    {
72      if (size(C.modules[i]) > 0)
73      {
74        addedStringCplx = "E^" + string(size(C.modules[i])) + "  <--  ";
75        sizeStringCplx = size(addedStringCplx);
76        addedStringDegrees = string(-C.shift + i -1);
77        sizeStringDegrees = size(addedStringDegrees);
78
79        if(sizeStringDegrees <= sizeStringCplx)
80        {
81          for (j = sizeStringDegrees + 1; j<= sizeStringCplx; j++)
82          {
83            addedStringDegrees = addedStringDegrees + " ";
84          }
85        }
86
87        if(sizeStringDegrees > sizeStringCplx)
88        {
89          for (j = sizeStringCplx + 1; j<= sizeStringDegrees; j++)
90          {
91            addedStringCplx = addedStringCplx + " ";
92          }
93        }
94
95        cplx = cplx + addedStringCplx;
96        degrees = degrees + addedStringDegrees;
97
98      }
99      else
100      {
101        addedStringCplx = "0" + "  <--  ";
102        sizeStringCplx = size(addedStringCplx);
103        addedStringDegrees = string(-C.shift + i -1);
104        sizeStringDegrees = size(addedStringDegrees);
105
106        if(sizeStringDegrees <= sizeStringCplx)
107        {
108          for (j = sizeStringDegrees + 1; j<= sizeStringCplx; j++)
109          {
110            addedStringDegrees = addedStringDegrees + " ";
111          }
112        }
113
114        if(sizeStringDegrees > sizeStringCplx)
115        {
116          for (j = sizeStringCplx + 1; j<= sizeStringDegrees; j++)
117          {
118            addedStringCplx = addedStringCplx + " ";
119          }
120        }
121
122
123        cplx = cplx + addedStringCplx;
124        degrees = degrees + addedStringDegrees;
125      }
126    }
127
128    if (size(C.modules[size(C.modules)]) > 0)
129    {
130      cplx = cplx + "E^" + string(size(C.modules[size(C.modules)]));
131      degrees = degrees + string(-C.shift + size(C.modules) -1);
132    }
133    else
134    {
135      cplx = cplx + "0";
136      degrees = degrees + string(-C.shift + size(C.modules) -1);
137    }
138
139    print(cplx);
140    print(degrees);
141  }
142}
143example
144{"EXAMPLE:";
145  echo = 2;
146  intvec c = 1,1;
147  def (S,E) = productOfProjectiveSpaces(c);
148  intvec low = -3,-3;
149  intvec high = 3,3;
150  setring(S);
151  module M = 0;
152  intmat gradeM[2][1] = -1,-1;
153  M = setModuleGrading(M,gradeM);
154  multigradedcomplex tate;
155  (E,tate) = tateResolution(M,low,high);
156  setring(E);
157  printMultigradedComplex(tate);
158}
159
160
161///////////////////////////////////////////////////////////////////////////////
162proc createMultigradedComplex(list reso)
163"USAGE:    createMultigradeComplex(reso); reso list
164PURPOSE:  transforms a list representing a multigraded complex into the type multigradedcomplex
165ASSUME:    first entry of reso is the homological shift, other entries are the differentials (note: with multigrading!)
166RETURN:    multigradedcomplex Reso
167"
168{
169  multigradedcomplex Reso;
170  Reso.shift = reso[1];
171  Reso.differentials = delete(reso,1);
172
173  // create the free modules corresponding to the differentials
174  list mods;
175  module M;
176  for (int i = 1; i <= size(Reso.differentials); i++)
177  {
178    M = freemodule(nrows(Reso.differentials[i]));
179    M = setModuleGrading(M,getModuleGrading(Reso.differentials[i]));
180    mods = insert(mods,M,size(mods));
181  }
182
183  // last special case
184  M = freemodule(ncols(Reso.differentials[size(Reso.differentials)]));
185  M = setModuleGrading(M,multiDeg(Reso.differentials[size(Reso.differentials)]));
186  mods = insert(mods,M,size(mods));
187  Reso.modules = mods;
188  return(Reso);
189}
190
191
192///////////////////////////////////////////////////////////////////////////////
193proc productOfProjectiveSpaces(intvec c)
194"USAGE:  productOfProjectiveSpaces(c); c intvec
195PURPOSE: creates two rings S and E corresponding to the product of projective spaces P^{c_1} x...x P^{c_t}
196ASSUME:  input are two integers or an intvec
197RETURN:  two rings S,E (homogeneous coordinate ring and the exterior algebra of P^{c_1} x P^{c_2} x...)
198"
199{
200  if (isSmaller(c-c,c) != 1)
201  {
202    ERROR("Entries of input vector have to be positive.")
203  }
204
205  int i,j,k;
206  ring S = 0,(x(0)(0..c[1])),dp;
207  for (i=2; i<= size(c); i++)
208  {
209    ring SHelp(i) = 0,(x(i-1)(0..c[i])),dp;
210    setring(SHelp(i));
211    for (j = 0; j<= c[i];j++)
212    {
213      S = addvarsTo(S,string(var(j+1)),0);
214    }
215  }
216
217  ring ES = 0,(e(0)(0..c[1])),dp;
218  for (i=2; i<= size(c); i++)
219  {
220    ring EHelp(i) = 0,(e(i-1)(0..c[i])),dp;
221    setring(EHelp(i));
222    for (j = 0; j<= c[i];j++)
223    {
224      ES = addvarsTo(ES,string(var(j+1)),0);
225    }
226  }
227  setring(ES);
228  ring E = Exterior();
229
230  // set multigrading
231  intmat grading[size(c)][sum(c)+ size(c)];
232  k = 1;
233  for (i = 1; i<= size(c); i++)
234  {
235    for (j = 1; j<= c[i] + 1 ; j++)
236    {
237      grading[i,k] = 1;
238      k = k+1;
239    }
240  }
241
242  setring(S);
243  setBaseMultigrading(grading);
244  setring(E);
245  setBaseMultigrading(-grading);
246
247  return(S,E);
248}
249example
250{"EXAMPLE:";
251   echo = 2;
252   intvec c = 1,2;
253   def (S,E) = productOfProjectiveSpaces(c);
254   print(S);
255   print(E);
256
257   intvec d = 2,1,2;
258   def (S2,E2) = productOfProjectiveSpaces(d);
259   print(S2);
260   print(E2);
261}
262
263
264///////////////////////////////////////////////////////////////////////////////
265proc truncateM(module M, intvec c)
266"USAGE:   truncateM(M,c); M module, c intvec
267PURPOSE: truncate M at c
268ASSUME:  @code{M} is multigraded S-module with S multigraded ring, c is an intvec of the right length
269RETURN:  module, the truncated module M_{>= c}
270NOTE:    Output is the truncated module (multigraded , grading is not shifted), works for arbitrary products
271EXAMPLE: example truncateM
272"
273{
274  if (gradingAndVectorCompatible(M,c) == 0)
275  {
276    ERROR("Grading of module and the vector are not compatible.")
277  }
278
279  intmat MGrading = getModuleGrading(M);
280  // determine the free module in which M lives
281  int n = nrows(M);
282
283  // compute the module with which we have to intersect the module M in order to obtain generators of the truncation
284  ideal F;
285  int i,j;
286  intvec d;
287  module T;
288  for (i = 1; i <= n; i++)
289  {
290    d = c - getColumnIntmat(MGrading,i);
291
292    for (j = 1; j<= size(d); j++)
293    {
294      if (d[j] < 0){d[j] = 0;}
295    }
296
297    F = multiDegBasis(d);
298    T = T + F*gen(i);
299  }
300
301  // now compute the intersection of M and T
302  module intersection = intersect(M,T);
303  intersection = setModuleGrading(intersection,MGrading);
304  return(intersection);
305}
306example
307{"EXAMPLE:";
308   echo = 2;
309   intvec c = 1,1,1;
310   def(S,E) = productOfProjectiveSpaces(c);
311   setring(S);
312   intmat grading[3][2] = 0,0,0,0,0,0;
313   module te = freemodule(2);
314   te = setModuleGrading(te,grading);
315   intvec c = 1,1,1;
316   module Mtrunc = truncateM(te,c);
317   Mtrunc;
318   getModuleGrading(Mtrunc);
319   multiDeg(Mtrunc);
320}
321
322
323///////////////////////////////////////////////////////////////////////////////
324proc truncateCoker(module M, intvec c)
325"USAGE:   truncateCoker(M,c);  M module, c intvec
326PURPOSE: truncate cokernel coker(M) at the multidegree c
327RETURN:  module, which is a presentation matrix of the truncation of coker(M) at c
328EXAMPLE: example truncateCoker
329"
330{
331  if (gradingAndVectorCompatible(M,c) == 0)
332  {
333    ERROR("Grading of module and the vector are not compatible.")
334  }
335
336  module SMod = freemodule(nrows(M));
337  SMod = setModuleGrading(SMod,getModuleGrading(M));
338  module result = prune(multiDegModulo(truncateM(SMod,c),truncateM(M,c)));
339  return(result);
340}
341example
342{"EXAMPLE:";
343  echo = 2;
344  // example 1
345  intvec c1 = 1,1,1;
346  def(S1,E1) = productOfProjectiveSpaces(c1);
347  setring(S1);
348  module M1= 0;
349  intmat grading1[3][1] = 0,0,0;
350  M1 = setModuleGrading(M1,grading1);
351  truncateCoker(M1,c1);
352
353  // example 2
354  intvec c2 = 1,1;
355  def (S2,E2) = productOfProjectiveSpaces(c2);
356  setring(S2);
357  module M2 = 0;
358  intmat grading2[2][1] = 0,0;
359  M2 = setModuleGrading(M2,grading2);
360  truncateCoker(M2,c2);
361}
362
363
364///////////////////////////////////////////////////////////////////////////////
365proc symExt(matrix m)
366"USAGE:  symExt(m); m matrix
367PURPOSE: computes differential R(M_0) -> R(M_1) for the module M over S corresponding to the linear presentation matrix m, however, in order to
368     get the result, m has to be fetched to the exterior algebra E
369ASSUME:  m a matrix, linear presentation matrix over S; Note: also works for nonlinear matrices, but makes no sense to use it in this case
370RETURN:  matrix B representing R(M_0) -> R(M_1)
371NOTE:    output lives in S (not as in Macaulay2 in the ring E, to get the same result, just fetch the matrix to E)
372EXAMPLE: example symExt
373"
374{
375  matrix MT = transpose(jacobM(m));
376  matrix JN = syz(MT);
377  matrix ML[nvars(basering)][1] = maxideal(1);
378  matrix A = transpose(outer(ML,unitmat(nrows(m))));
379  matrix B = transpose(A*JN);
380  return(B);
381}
382example
383{"EXAMPLE:";
384   echo = 2;
385   intvec c = 1,2;
386   def (S,E) = productOfProjectiveSpaces(c);
387   setring(S);
388   matrix m[4][2] = x(0)(0), x(1)(0),x(0)(1),0,0,x(1)(1), 0,x(1)(2);
389   matrix A = symExt(m);
390   print(A);
391   setring(E);
392   print(fetch(S,A));
393}
394
395
396///////////////////////////////////////////////////////////////////////////////
397proc sufficientlyPositiveMultidegree(module M)
398"USAGE:  sufficientlyPositiveMultidegree(M); M module
399PURPOSE: computes a sufficiently positive multidegree for coker(M)
400ASSUME:  M is multigraded S-module
401RETURN:  intvec that is sufficiently positive for M
402EXAMPLE: example sufficientlyPositiveMultidegree
403"
404{
405  if (M ==0)
406  {
407    list T = M;
408  }
409  else
410  {
411    module free = freemodule(nrows(M));
412    free = setModuleGrading(free, getModuleGrading(M));
413    list T = multiDegResolution(multiDegModulo(free,M),0,1);
414  }
415  int lengthResolution = size(T);
416  matrix lowerbounds;
417  intvec mulReg;
418
419  for (int i = 1; i<= lengthResolution; i++)
420  {
421    lowerbounds = concat(lowerbounds, matrix(getModuleGrading(T[i])));
422  }
423
424  lowerbounds = submat(lowerbounds,1..nrows(lowerbounds),2..ncols(lowerbounds));
425  mulReg = int(max(lowerbounds[1,1..ncols(lowerbounds)]));
426  for (int j = 2; j <= nrows(lowerbounds); j++)
427  {
428    mulReg = mulReg, int(max(lowerbounds[j,1..ncols(lowerbounds)]));
429  }
430  return(mulReg);
431}
432example
433{"EXAMPLE:";
434  echo = 2;
435  // example 1
436  intvec c1 = 1,2;
437  def (S1,E1) = productOfProjectiveSpaces(c1);
438  setring(S1);
439  module M1 = x(0)(0),x(1)(0)^3 + x(1)(1)^3 +x(1)(2)^3;
440  intmat grading1[2][1] = 0,0;
441  M1 = setModuleGrading(M1,grading1);
442  sufficientlyPositiveMultidegree(M1);
443
444  // example 2
445  intvec c2 = 1,1;
446  def (S2,E2) = productOfProjectiveSpaces(c2);
447  setring(S2);
448  intmat grading2[2][1] = -1,-1;
449  module M2 = 0;
450  M2 = setModuleGrading(M2,grading2);
451  sufficientlyPositiveMultidegree(M2);
452
453  // example 3
454  intvec c3 = 1,1,1;
455  def (S3,E3) = productOfProjectiveSpaces(c3);
456  setring(S3);
457  module M3 = 0;
458  intmat grading3[3][1] = -1,-1,-1;
459  M3 = setModuleGrading(M3,grading3);
460  sufficientlyPositiveMultidegree(M3);
461}
462
463
464///////////////////////////////////////////////////////////////////////////////
465proc tateResolution(module M, intvec low, intvec high)
466"USAGE:  tateResolution(M,low,high); M module, L list, low intvec, high intvec
467PURPOSE: compute tate resolution of coker(M) where M is Z^t-graded S-module
468ASSUME:   M a module over multigraded ring S
469RETURN:  (E,tate), tate a multigradedcomplex, E the ring in which tate has to be viewed,
470     however note that tate is not ring dependent
471EXAMPLE: example tateResolution
472"
473{
474  if (gradingAndVectorCompatible(M,low) == 0)
475  {
476    ERROR("Grading of module and the vectors are not compatible.");
477  }
478  if (isLEQ(low,high) == 0)
479  {
480    ERROR("intvec low has to be lower or equal to the intvec high.");
481  }
482
483  intvec dims = getDimensionVector(getVariableWeights(basering));
484  def (S2,E) = productOfProjectiveSpaces(dims);
485  def S = basering;
486  intvec regs = sufficientlyPositiveMultidegree(M);
487
488  intvec hi = max(regs[1],high[1]+1);
489  for (int i = 2; i <= size(regs); i++)
490  {
491    hi = hi, max(regs[i],high[i]+1);
492  }
493
494  // now truncate M at hi
495  module N = truncateCoker(M,hi);
496
497  matrix A = symExt(N);
498
499  setring(E);
500  matrix A = fetch(S,A);
501  intmat ASourceGrading[size(hi)][ncols(A)];
502  intmat ATargetGrading[size(hi)][nrows(A)] = getTargetGrading(A,ASourceGrading);
503  module AMod = setModuleGrading(module(A),ATargetGrading);
504  AMod = twist(AMod,-hi);
505
506  int n = sum(hi)-sum(low) - size(low) + 2;
507  def reso = multiDegResolution(AMod,n,1);
508  reso = insert(reso,0);
509  multigradedcomplex tate = createMultigradedComplex(reso);
510
511  // for output as in M2, comment the delete commands out and shift by sum(hi)- size(regs) + 2 instead
512  tate = deleteFirstEntry(tate);
513  tate = deleteFirstEntry(tate);
514  tate = shift(tate,sum(hi)-size(regs));
515
516  return(E,tate);
517
518}
519example
520{"EXAMPLE:";
521  echo = 2;
522  // example 1
523  intvec c1 = 1,1,1;
524  intvec low1 = 0,0,0;
525  intvec high1 = 0,1,0;
526  def (S1,E1) = productOfProjectiveSpaces(c1);
527  setring(S1);
528  module M1 = 0;
529  intmat grading1[3][1] = -1,-1,-1;
530  M1 = setModuleGrading(M1,grading1);
531  multigradedcomplex tate1;
532  (E1,tate1) = tateResolution(M1,low1,high1);
533  setring(E1);
534  tate1;
535  tate1.differentials;
536
537  // example 2
538  intvec c2 = 1,2;
539  def (S2,E2) = productOfProjectiveSpaces(c2);
540  setring(S2);
541  intvec low2 = -3,-3;
542  intvec high2 = 0,0;
543  module M2 = x(0)(0),x(1)(0)^3 + x(1)(1)^3 +x(1)(2)^3;;
544  intmat grading2[2][1] = 0,0;
545  M2 = setModuleGrading(M2,grading2);
546  multigradedcomplex tate2;
547  (E2,tate2) = tateResolution(M2,low2,high2);
548  setring(E2);
549  tate2;
550
551  // example 3
552  intvec c3 = 1,1;
553  def (S3,E3) = productOfProjectiveSpaces(c3);
554  intvec low3 = -3,-3;
555  intvec high3 = 3,3;
556  setring(S3);
557  module M3 = 0;
558  intmat grading3[2][1] = -1,-1;
559  M3 = setModuleGrading(M3,grading3);
560  multigradedcomplex tate3;
561  (E3,tate3) = tateResolution(M3,low3,high3);
562  setring(E3);
563  tate3;
564}
565
566
567///////////////////////////////////////////////////////////////////////////////
568proc cohomologyMatrix(module M, intvec low, intvec high)
569"USAGE:  cohomologyMatrix(M,L,low,high); M module, L list, low intvec, high intvec
570PURPOSE: computes the cohomology matrix of the sheaf corresponding to coker(M)
571ASSUME:  M module over S, L list of two rings S and E (e.g. result of productOfProjectiveSpaces)
572         first entry L[1] = S and L[2] = E, integer vectors low <= high
573RETURN:  ring Z in which cohomology matrix lives, it is exported in the variable cohomologymat, cohomologymat covers all cohomology
574     groups of twists in the range between low and high
575EXAMPLE: example cohomologyMatrix
576"
577{
578  if (gradingAndVectorCompatible(M,low) == 0)
579  {
580    ERROR("Grading of module and the vectors are not compatible.");
581  }
582  if (isLEQ(low,high) == 0)
583  {
584    ERROR("intvec low has to be lower or equal to the intvec high.")
585  }
586  if (size(low) != 2)
587  {
588    ERROR("cohomologyMatrixCoker only works for product of two projective spaces, i.e. Z^2 gradings.";)
589  }
590
591  def (E,tate) = tateResolution(M,low, high);
592  setring(E);
593  list reso = tate.differentials;
594  int n = nvars(E)-2; // i.e. if P = P^{n_1} x P^{n_2}, then n = n_1+n_2
595
596  int i,j,k,d,numhk;
597  ring Z = 0,h,dp; // in this ring we compute the cohomologymatrix
598  setring(Z);
599  matrix cohomologymat[high[2]-low[2]+1][high[1]-low[1]+1];
600
601  for (i = low[1]; i <= high[1]; i++)  //iterate over rows
602  {
603    for (j = low[2]; j <= high[2]; j++)
604    {
605      for (k=0; k<= n; k++)
606      {
607        d = -i-j-k;
608        setring(E);
609        numhk = 0;
610        if (d+1+ tate.shift>= 1 && d+1+tate.shift <= size(tate.modules))
611        {
612          numhk = countMultiDegree(intvec(i,j),getModuleGrading(tate.modules[d+1+tate.shift]));
613        }
614        setring(Z);
615        cohomologymat[high[2]-j+1,-low[1]+i+1] = cohomologymat[high[2]-j+1,-low[1]+i+1] + numhk * h^k;
616      }
617    }
618  }
619  export(cohomologymat);
620  return(Z);
621}
622example
623{"EXAMPLE:";
624  echo = 2;
625  // example 1
626  intvec c1 = 1,1;
627  def (S1,E1) = productOfProjectiveSpaces(c1);
628  intvec low1 = -3,-3;
629  intvec high1 = 3,3;
630  setring(S1);
631  module M1 = 0;
632  intmat grading1[2][1] = -1,-1;
633  M1 = setModuleGrading(M1,grading1);
634  ring Z1 = cohomologyMatrix(M1,low1,high1);
635  setring(Z1);
636  print(cohomologymat);
637
638  // example 2
639  intvec c2 = 1,2;
640  def (S2,E2) = productOfProjectiveSpaces(c2);
641  intvec low2 = -3,-3;
642  intvec high2 = 0,0;
643  setring(S2);
644  module M2 = 0;
645  intmat grading2[2][1] = 0,0;
646  M2 = setModuleGrading(M2,grading2);
647  ring Z2 = cohomologyMatrix(M2,low2,high2);
648  setring(Z2);
649  print(cohomologymat);
650
651  // example 3
652  setring(S2);
653  module M3 = x(0)(0),x(1)(0)^3 + x(1)(1)^3 +x(1)(2)^3;
654  intmat grading3[2][1] = 0,0;
655  M3 = setModuleGrading(M3,grading3);
656  ring Z3 = cohomologyMatrix(M3,low2,high2);
657  setring(Z3);
658  print(cohomologymat);
659}
660
661
662///////////////////////////////////////////////////////////////////////////////
663proc cohomologyMatrixFromResolution(multigradedcomplex T, intvec low, intvec high)
664"USAGE:  cohomologyMatrixFromResolution(T,low,high); T multigradedcomplex, low intvec, high intvec
665PURPOSE: computes the cohomology matrix corresponding to the multigraded complex T (part of a Tate resolution)
666ASSUME:  T is a multigraded complex representing a part of a Tate resolution (for example output of tateResolution), basering is E
667RETURN:  ring Z in which cohomology matrix lives, it is exported in the variable cohomologymat, cohomologymat stores information in the range between
668     low and high
669EXAMPLE: example cohomologyMatrixFromResolution
670"
671{
672  if (size(T.modules[1]) == 0 && size(T.modules) > 1)
673  {
674    if (gradingAndVectorCompatible(T.modules[2],low) == 0)
675    {
676      ERROR("Grading of Tate resolution and the vectors are not compatible.");
677    }
678  }
679  else
680  {
681    if (gradingAndVectorCompatible(T.modules[1],low) == 0)
682    {
683      ERROR("Grading of Tate resolution and the vectors are not compatible.");
684    }
685  }
686  if (isLEQ(low,high) == 0)
687  {
688    ERROR("intvec low has to be lower or equal to the intvec high.");
689  }
690  if (size(low) != 2)
691  {
692    ERROR("cohomologyMatrixCoker only works for product of two projective spaces, i.e. Z^2 gradings.");
693  }
694
695  ring E = basering;
696  int n = nvars(E)-2; // i.e. if P = P^{n_1} x P^{n_2}, then n = n_1+n_2
697  // now compute the cohomology table from the tate resolution
698  int i,j,k,d,numhk;
699  ring Z = 0,h,dp; // in this ring we compute the cohomologymatrix
700  setring(Z);
701  matrix cohomologymat[high[2]-low[2]+1][high[1]-low[1]+1];
702
703  for (i = low[1]; i <= high[1]; i++)  //iterate over rows
704  {
705    for (j = low[2]; j <= high[2]; j++)
706    {
707      // compute the entry (i,j) of the cohomologymatrix
708      for (k=0; k<= n; k++)
709      {
710        // compute coefficient of h^k in entry (i,j)
711        // find these information in the term d = -i-j-k
712        d = -i-j-k;
713        // as we don't shift the resolution by some homological degree, the dth term corresponds
714        // to the (d+1+T.shift)th entry in T
715        setring(E);
716        numhk = 0;
717        if (d+1+T.shift >= 1 && d+1+T.shift <= size(T.modules))
718        {
719          if (size(T.modules[d+1+T.shift]) == 0)
720          {
721            numhk = 0;
722          }
723          else
724          {
725            numhk = countMultiDegree(intvec(i,j),getModuleGrading(T.modules[d+1+T.shift]));
726          }
727        }
728        setring(Z);
729        cohomologymat[high[2]-j+1,-low[1]+i+1] = cohomologymat[high[2]-j+1,-low[1]+i+1] + numhk * h^k;
730      }
731    }
732  }
733  export(cohomologymat);
734  return(Z);
735}
736example
737{"EXAMPLE:";
738  echo = 2;
739  intvec c = 1,1;
740  def (S,E) = productOfProjectiveSpaces(c);
741  intvec low = -3,-3;
742  intvec high = 3,3;
743  setring(S);
744  module M = 0;
745  intmat grading[2][1] = -1,-1;
746  M = setModuleGrading(M,grading);
747  multigradedcomplex tate;
748  (E,tate) = tateResolution(M,low,high);
749  setring(E);
750  ring Z = cohomologyMatrixFromResolution(tate,low,high);
751  setring(Z);
752  print(cohomologymat);
753}
754
755
756//////////////////////////////////////////////////////////////////////////
757proc eulerPolynomialTable(module M, intvec low, intvec high)
758"USAGE:  eulerPolynomialTable(M,low,high); M module, L list, low intvec, high intvec
759PURPOSE: computes hash table of euler polynomials of twists of coker(M) in the range between low and high
760ASSUME:  M module, note that at the moment M is a module over S,
761RETURN:  (Z,eulerpolynomialtable), where eulerpolynomialtable is a hash table with entries in the ring Z = ZZ[h]
762NOTE:    this function works for arbitrary products P^{n_1} x \cdots x P^{n_t} and corresponding Z^t-gradings, entries can be accessed via
763     eulerpolynomialtable*(a_1,...,a_t) where a=(a_1,...,a_t) is a multidegree betweeen low and high
764EXAMPLE: example eulerPolynomialTable
765"
766{
767  if (gradingAndVectorCompatible(M,low) == 0)
768  {
769    ERROR("Grading of module and the vector low are not compatible.")
770  }
771  if (isLEQ(low,high) == 0)
772  {
773    ERROR("intvec low has to be lower or equal to the intvec high.")
774  }
775
776  int n = nvars(basering)-size(low);
777  def (E,tate) = tateResolution(M,low, high);
778  setring(E);
779
780  int i,j,k,d,numhk;
781  ring Z = 0,h,dp; // in this ring we compute the eulerpolynomialtable
782  setring(Z);
783  HashTable eulerpolynomialtable;
784  poly eulerpoly;
785
786  matrix A = vectorsLEQ(high-low);
787  intvec entry;
788  for (i = 1; i<= ncols(A); i++)
789  {
790    entry = int(A[1,i]);
791
792    for (k = 2; k <= nrows(A); k++)
793    {
794      entry = entry,int(A[k,i]);
795    }
796    entry = entry +low;
797    // now compute euler polynomial
798    setring(Z);
799    eulerpoly = 0;
800
801    for (k=0; k<= n; k++)
802    {
803      d = -sum(entry)-k;
804      setring(E);
805      numhk = 0;
806      if (d+1+tate.shift >= 1 && d+1+tate.shift <= size(tate.modules))
807      {
808        numhk = countMultiDegree(entry,getModuleGrading(tate.modules[d+1+tate.shift]));
809      }
810      setring(Z);
811      eulerpoly = eulerpoly +  numhk * h^k;
812    }
813    eulerpolynomialtable  = eulerpolynomialtable + hashTable(list(entry),list(eulerpoly));
814  }
815  return(Z,eulerpolynomialtable);
816}
817example
818{"EXAMPLE:";
819  echo = 2;
820  // example 1
821  intvec c1 = 1,1;
822  def (S1,E1) = productOfProjectiveSpaces(c1);
823  intvec low1 = -3,-3;
824  intvec high1 = 3,3;
825  setring(S1);
826  module M1 = 0;
827  intmat grading1[2][1] = -1,-1;
828  M1 = setModuleGrading(M1,grading1);
829  def (Z1,eulerTable1) = eulerPolynomialTable(M1,low1,high1);
830  setring(Z1);
831  print(eulerTable1);
832  eulerTable1*low1;
833
834  setring(S1);
835  ring Z = cohomologyMatrix(M1,low1,high1);
836  setring(Z);
837  print(cohomologymat);
838
839  // example 2
840  intvec c2 =  1,1,1;
841  def (S2,E2) = productOfProjectiveSpaces(c2);
842  setring(S2);
843  intvec low2 = 0,0,0;
844  intvec high2 = 1,1,1;
845  module M2 = 0;
846  intmat grading2[3][1] = -1,-1,-1;
847  M2 = setModuleGrading(M2,grading2);
848  def (Z2,eulerTable2) = eulerPolynomialTable(M2,low2,high2);
849  setring(Z2);
850  print(eulerTable2);
851}
852
853
854//////////////////////////////////////////////////////////////////////////
855proc cohomologyHashTable(module M, intvec low, intvec high)
856"USAGE:  cohomologyHashTable(M,L,low,high); M module, low intvec, high intvec
857PURPOSE: computes hashtable of sheaf cohomology groups of twists in the range between between low and high corresponding to coker(M)
858ASSUME:  M module representing a sheaf F on the product of t projective spaces,
859     note that at the moment M is a module over S,
860RETURN:  cohomologytable where cohomologytable is a hash table with
861       integer vectors in ZZ^{t+1} as keys, entries can be accessed via cohomologytable*(c_1,...,c_t,i) = dim(H^i(F(c_1,...,c_t)))
862NOTE:    this function works for arbitrary products P^{n_1} x \cdots x P^{n_t} and corresponding Z^t-gradings
863EXAMPLE: example cohomologyHashTable
864"
865{
866  if (gradingAndVectorCompatible(M,low) == 0)
867  {
868    ERROR("Grading of module and the vector low are not compatible.")
869  }
870  if (isLEQ(low,high) == 0)
871  {
872    ERROR("intvec low has to be lower or equal to the intvec high.")
873  }
874
875  int n = nvars(basering)-size(low); // ie if P = P^{n_1} x \cdtos x P^{n_t}, then n = n_1 + \cdots + n_t
876  def (E,tate) = tateResolution(M,low, high);
877  setring(E);
878  int i,j,k,d,numhk;
879  HashTable cohomologytable;
880
881  matrix A = vectorsLEQ(high-low);
882  intvec entry;
883  for (i = 1; i<= ncols(A); i++)
884  {
885    entry = int(A[1,i]);
886
887    for (k = 2; k <= nrows(A); k++)
888    {
889      entry = entry,int(A[k,i]);
890    }
891    entry = entry +low;
892
893    for (k=0; k<= n; k++)
894    {
895      // compute vorfaktor of h^k in entry (i,j)
896      // find these information in the term d = -i-j-k
897      d = -sum(entry)-k;
898      // as we don't shift the resolution by some homological degree, the dth term corresponds
899      // to the (d+tate.shift)th entry in reso
900      setring(E);
901      numhk = 0;
902      if (d+1+tate.shift >= 1 && d+1+tate.shift <= size(tate.modules))
903      {
904        numhk = countMultiDegree(entry,getModuleGrading(tate.modules[d+1+tate.shift]));
905        cohomologytable  = cohomologytable + hashTable(list(intvec(entry,k)),list(numhk));
906      }
907    }
908  }
909
910  return(cohomologytable);
911}
912example
913{"EXAMPLE:";
914  echo = 2;
915  intvec c = 1,1;
916  def (S,E) = productOfProjectiveSpaces(c);
917  intvec low = -3,-3;
918  intvec high = 3,3;
919  setring(S);
920  module M = 0;
921  intmat grading[2][1] = -1,-1;
922  M = setModuleGrading(M,grading);
923  def cohomologytable = cohomologyHashTable(M,low,high);
924  print(cohomologytable);
925  intvec d = 3,3,0;
926  cohomologytable*d;
927
928  def (Z,eulerTable) = eulerPolynomialTable(M,low,high);
929  setring(Z);
930  print(eulerTable);
931}
932
933
934//////////////////////////////////////////////////////////////////////////
935proc twist(module M,intvec c)
936"USAGE:  twist(M,c); M module, c intvec
937PURPOSE: twists the module M by c
938ASSUME:  M is a multigraded module
939RETURN:  M with the new grading
940EXAMPLE: example twist
941"
942{
943  if (gradingAndVectorCompatible(M,c) == 0)
944  {
945    ERROR("Grading of module and the vector are not compatible.")
946  }
947  intmat MGrading = getModuleGrading(M);
948  MGrading = MGrading - matrixWithSpecificEntries(nrows(MGrading),ncols(MGrading),c);
949  module Mtwisted = setModuleGrading(M,MGrading);
950  return(Mtwisted);
951}
952example
953{"EXAMPLE:";
954  echo = 2;
955  intvec c = 1,1;
956  def (S,E) = productOfProjectiveSpaces(c);
957  setring(S);
958  module M = freemodule(2);
959  intmat gradeM[2][2] = 0,1,0,1;
960  M = setModuleGrading(M,gradeM);
961  getModuleGrading(M);
962  intvec c = 2,2;
963  module Mtwist = twist(M,c);
964  getModuleGrading(Mtwist);
965}
966
967
968///////////////////////////////////////////////////////////////////////////////
969proc beilinsonWindow(multigradedcomplex T)
970"USAGE:  beilinsonWindow(T); T multigradedcomplex
971PURPSOSE:compute the subquotient complex of T consisting of summands generated in degrees 0 <= a <= n
972ASSUME:  T is a multigraded complex of free E-modules
973RETURN:  multigradedcomplex, the Beilinson window of T
974NOTE:    The returend summands are the only ones that contribute to the Beilinson monad.
975EXAMPLE: example beilinsonWindow
976"
977{
978  int i,j;
979  intvec b,c;
980  matrix A,B;
981  intmat grad;
982
983  intvec n = getDimensionVector(getVariableWeights(basering));
984
985  // go through all modules in the complex
986  for (i = size(T.modules); i >= 1; i--)
987  {
988    c = inBeilinsonWindow(getModuleGrading(T.modules[i]),n);
989    if (size(c)>1)
990    {
991      // need to determine the module grading
992      T.modules[i] = setModuleGrading(freemodule(size(c)-1),deleteColumnsIntmat(getModuleGrading(T.modules[i]),c));
993
994      if(i > 2 && i <= size(T.differentials))
995      {
996        //delete rows and columns in the corresponding maps
997        // delete rows in T.differentials[i] and adjust the module grading
998        A = matrix(T.differentials[i]);
999        A = deleteRows(A,c);
1000        T.differentials[i] = setModuleGrading(module(A),deleteColumnsIntmat(getModuleGrading(T.differentials[i]),c));
1001        //delete columns in T.differentials[i-1] if i > 2
1002        //delete columns in T.differentials[i-1]
1003        A = matrix(T.differentials[i-1]);
1004        A = deleteColumns(A,c);
1005        T.differentials[i-1] = setModuleGrading(module(A),getModuleGrading(T.differentials[i-1]));
1006      }
1007      else
1008      {
1009        if(i == 1)
1010        {
1011          //only have to delete rows
1012          A = matrix(T.differentials[i]);
1013          A = deleteRows(A,c);
1014          T.differentials[i] = setModuleGrading(module(A),deleteColumnsIntmat(getModuleGrading(T.differentials[i]),c));
1015        }
1016        else
1017        {
1018          // only have to delete columns
1019          A = matrix(T.differentials[i-1]);
1020          A = deleteColumns(A,c);
1021          T.differentials[i-1] = setModuleGrading(module(A),getModuleGrading(T.differentials[i-1]));
1022        }
1023      }
1024    }
1025    else
1026    {
1027      T.modules[i] = freemodule(0);
1028    }
1029
1030  }
1031
1032  T = deleteZerosMultigradedComplex(T);
1033
1034  return(T);
1035}
1036example
1037{"EXAMPLE:";
1038  echo = 2;
1039  intvec f = 1,1;
1040  def (S,E) = productOfProjectiveSpaces(f);
1041  intvec low = -3,-3;
1042  intvec high = 3,3;
1043  setring(S);
1044  module M = 0;
1045  intmat MGrading[2][1] = -1,-1;
1046  M = setModuleGrading(M,MGrading);
1047  multigradedcomplex tate;
1048  (E,tate) = tateResolution(M,low,high);
1049  setring(E);
1050  multigradedcomplex W = beilinsonWindow(tate);
1051  W;
1052
1053  intvec c = 1,1,1;
1054  intvec low2 = 0,0,0;
1055  intvec high2 = 0,1,0;
1056  def (S2,E2) = productOfProjectiveSpaces(c);
1057  setring(S2);
1058  module M2 = 0;
1059  intmat gradeM[3][1] = -1,-1,-1;
1060  M2 = setModuleGrading(M2,gradeM);
1061  multigradedcomplex tate2;
1062  (E2,tate2) = tateResolution(M2,low2,high2);
1063  setring(E2);
1064  multigradedcomplex W2 = beilinsonWindow(tate2);
1065  W2;
1066}
1067
1068
1069///////////////////////////////////////////////////////////////////////////////
1070proc regionComplex(multigradedcomplex T, intvec d, intvec I, intvec J, intvec K)
1071"USAGE:  regionComplex(T,d,I,J,K); T multigradedcomplex, d intvec, I intvec, J intvec, K intvec
1072PURPOSE: compute the region complex of T w.r.t. the sets I,J,K and the vector d
1073ASSUME:  I,J,K are intvecs representing disjoint subsets of {1,...,t}, T is a complex in ring E, zero represents the empty set
1074RETURN:  multigraded complex which is the region complex T_d(I,J,K) of T
1075EXAMPLE: example regionComplex
1076"
1077{
1078  if (isDisjoint(I,J,K) == 0)
1079  {
1080    ERROR("I,J,K have to be disjoint.");
1081  }
1082
1083  int i;
1084  intvec c;
1085  matrix A,B;
1086  intmat grad;
1087
1088  // go through all modules in the complex T
1089  for (i = size(T.modules); i>= 1; i--)
1090  {
1091    c = goodColumns(getModuleGrading(T.modules[i]),d,I,J,K);
1092    // analogous procedure to beilinsonWindow
1093    if (size(c)>1)
1094    {
1095      // need to determine the module grading
1096      T.modules[i] = setModuleGrading(freemodule(size(c)-1),deleteColumnsIntmat(getModuleGrading(T.modules[i]),c));
1097
1098      if(i > 2 && i <= size(T.differentials))
1099      {
1100        //delete rows and columns in the corresponding maps
1101        // delete rows in T.differentials[i] and adjust the module grading
1102        A = matrix(T.differentials[i]);
1103        A = deleteRows(A,c);
1104        T.differentials[i] = setModuleGrading(module(A),deleteColumnsIntmat(getModuleGrading(T.differentials[i]),c));
1105        //delete columns in T.differentials[i-1] if i > 2
1106        //delete columns in T.differentials[i-1]
1107        A = matrix(T.differentials[i-1]);
1108        A = deleteColumns(A,c);
1109        T.differentials[i-1] = setModuleGrading(module(A),getModuleGrading(T.differentials[i-1]));
1110      }
1111      else
1112      {
1113        if(i == 1)
1114        {
1115          //only have to delete rows
1116          A = matrix(T.differentials[i]);
1117          A = deleteRows(A,c);
1118          T.differentials[i] = setModuleGrading(module(A),deleteColumnsIntmat(getModuleGrading(T.differentials[i]),c));
1119        }
1120        else
1121        {
1122          // only have to delete columns
1123          A = matrix(T.differentials[i-1]);
1124          A = deleteColumns(A,c);
1125          T.differentials[i-1] = setModuleGrading(module(A),getModuleGrading(T.differentials[i-1]));
1126        }
1127      }
1128    }
1129    else
1130    {
1131      T.modules[i] = freemodule(0);
1132    }
1133  }
1134  // delete not necessary zeros in T
1135  T = deleteZerosMultigradedComplex(T);
1136  return(T);
1137}
1138example
1139{"EXAMPLE:";
1140  echo = 2;
1141  intvec f = 1,1;
1142  def (S,E) = productOfProjectiveSpaces(f);
1143  intvec low = -3,-3;
1144  intvec high = 3,3;
1145  setring(S);
1146  module M = 0;
1147  intmat MGrading[2][1] = -1,-1;
1148  M = setModuleGrading(M,MGrading);
1149  multigradedcomplex tate;
1150  (E,tate) = tateResolution(M,low,high);
1151  setring(E);
1152  tate;
1153
1154  ring Z = cohomologyMatrixFromResolution(tate,low,high);
1155  setring(Z);
1156  print(cohomologymat);
1157
1158  setring(E);
1159  intvec  c= 0,-3;
1160  intvec I = 0;
1161  intvec J = 0,1;
1162  intvec K = 0,2;
1163  multigradedcomplex U = regionComplex(tate,c,I,J,K);
1164  U;
1165
1166  Z = cohomologyMatrixFromResolution(U,low,high);
1167  setring(Z);
1168  print(cohomologymat);
1169
1170  setring(E);
1171  multigradedcomplex V = regionComplex(tate,c,I,J,J);
1172}
1173
1174
1175///////////////////////////////////////////////////////////////////////////////
1176proc strand(multigradedcomplex T, intvec c, intvec J)
1177"USAGE:  strand(T,c,J)
1178PURPOSE: compute the strand of T w.r.t. the set J and the vector c
1179RETURN:  subquotient complex of T which is the strand of T
1180EXAMPLE: example strand
1181"
1182{
1183  // if first entry of I is not 0, then add 0 for better compatibility
1184  if (J[1] != 0)
1185  {
1186    J = 0,J;
1187  }
1188  intvec I,K;
1189
1190  return(regionComplex(T,c,I,J,K));
1191}
1192example
1193{"EXAMPLE:";
1194  echo = 2;
1195  intvec f = 1,1;
1196  def (S,E) = productOfProjectiveSpaces(f);
1197  intvec low = -3,-3;
1198  intvec high = 3,3;
1199  setring(S);
1200  module M = 0;
1201  intmat MGrading[2][1] = -1,-1;
1202  M = setModuleGrading(M,MGrading);
1203  multigradedcomplex tate;
1204  (E,tate) = tateResolution(M,low,high);
1205  setring(E);
1206
1207  ring Z = cohomologyMatrixFromResolution(tate,low,high);
1208  setring(Z);
1209  print(cohomologymat);
1210
1211  setring(E);
1212  intvec  c= 0,-3;
1213  intvec J = 1;
1214  multigradedcomplex U = strand(tate,c,J);
1215  U;
1216
1217  Z = cohomologyMatrixFromResolution(U,low,high);
1218  setring(Z);
1219  print(cohomologymat);
1220}
1221
1222
1223////////////////////////////////////////////////////////////////////////////
1224proc firstQuadrantComplex(multigradedcomplex T, intvec c)
1225"USAGE:  firstQuadrantComplex(T,c); T multigradedcomplex, c intvec
1226PURPOSE: compute the first quadrant complex of T w.r.t. the set J and the vector c
1227RETURN:  subquotient complex of T which is the first quadrand complex of T
1228"
1229{
1230  intvec K = 0,1..size(c);
1231  intvec I,J;
1232  return(regionComplex(T,c,I,J,K));
1233}
1234
1235
1236///////////////////////////////////////////////////////////////////////////////
1237proc lastQuadrantComplex(multigradedcomplex T, intvec c)
1238"USAGE:  lastQuadrantComplex(T,c); T multigradedcomplex, c intvec
1239PURPOSE: compute the last quadrant complex of T w.r.t. the set J and the vector c
1240RETURN:  subquotient complex of T which is the strand of T
1241"
1242{
1243  intvec I = 0,1..size(c);
1244  intvec J,K;
1245  return(regionComplex(T,c,I,J,K));
1246}
1247
1248
1249///////////////////////////////////////////////////////////////////////////////
1250proc sortedBases(int i)
1251"USAGE:  computes a list sortedB where in each entry k we have sortedB[k] = all monomials of degree k*e_i
1252      (sorted)
1253ASSUME: We are working over a multigraded ring
1254RETURN:  list sortedB
1255EXAMPLE: example sortedB
1256"
1257{
1258  intvec d = 1..nrows(getVariableWeights(basering));
1259  d = d-d;
1260  d[i] = 1;
1261  int j,n;
1262  n = countMultiDegree(d, getVariableWeights(basering));
1263  list sortedB;
1264  for (j = 0; j <= n; j++)
1265  {
1266    sortedB = insert(sortedB,multiDegBasis(j*d),size(sortedB));
1267  }
1268  return(sortedB);
1269}
1270example
1271{"EXAMPLE:";
1272  echo = 2;
1273  intvec f = 2,3;
1274  def (S,E) = productOfProjectiveSpaces(f);
1275  setring(E);
1276  list sortedB = sortedBases(1);
1277  sortedB;
1278}
1279
1280
1281///////////////////////////////////////////////////////////////////////////////
1282proc diffAntiCommutative(ideal I, ideal J)
1283"USAGE:  differentiate the second input by the first
1284ASSUME: We are working over anticommutative E
1285RETURN:  matrix D
1286EXAMPLE: example diffAntiCommutative
1287"
1288{
1289  matrix D = diff(I,J);
1290  //now have to correct the signs since Singular does not do it right...?
1291  int i,j;
1292  for (i = 1; i<= nrows(D); i++)
1293  {
1294    for(j = 1; j<=ncols(D);j++)
1295    {
1296      if (D[i,j]*I[i] == -J[j])
1297      {
1298        D[i,j] = -D[i,j];
1299      }
1300    }
1301  }
1302  return(D);
1303}
1304example
1305{"EXAMPLE:";
1306  echo = 2;
1307  intvec f = 2,3;
1308  def (S,E) = productOfProjectiveSpaces(f);
1309  setring(E);
1310  list sortedB = sortedBases(1);
1311  sortedB[2];
1312  sortedB[3];
1313
1314  print(diff(sortedB[],sortedB[3]));
1315
1316  print(diffAntiCommutative(sortedB[2],sortedB[3]));
1317}
1318
1319
1320///////////////////////////////////////////////////////////////////////////////
1321proc koszulmap(int i, list sortedB)
1322"USAGE:  computes the ith koszul map
1323ASSUME: basering ist E, assume sortedB is a list of sorted bases (result of sortedBases)
1324NOTE: in contrast to the function in M2 we remain in the ring E, to get the real koszul map have to substitute vars of S
1325RETURN:  matrix K
1326EXAMPLE: example koszulmap
1327"
1328{
1329  matrix D;
1330  if (i == 0)
1331  {
1332    D = matrix(0);
1333  }
1334  else
1335  {
1336    intvec d = multiDeg(sortedB[2][1]);
1337    D = diffAntiCommutative(sortedB[i],sortedB[i+1]);
1338  }
1339  return(D);
1340}
1341example
1342{"EXAMPLE:";
1343  echo = 2;
1344  intvec f = 2,3;
1345  def (S,E) = productOfProjectiveSpaces(f);
1346  setring(E);
1347  list sortedB = sortedBases(2);
1348
1349  matrix K1 = koszulmap(1,sortedB);
1350  matrix K2 = koszulmap(2,sortedB);
1351
1352  setring(S);
1353
1354  print(fetch(E,K1));
1355  print(fetch(E,K2));
1356}
1357
1358
1359///////////////////////////////////////////////////////////////////////////////
1360proc simpleBeilinsonBundle(int a, int w, list L)
1361"USAGE:  computes a basic beilinson bundle (i.e. the pullback of a single projective space factor),
1362      with notation in the paper: it computes \wedge^a U_w
1363ASSUME:  the current basering is S, L ist list with entry E (ring);
1364    if P = P^{n_1} x....xP^{n_t}, then 1<=w <= t and 0 <= a <= n_w,
1365    if the inputs are not in this range, then the zero module is returned
1366NOTE:
1367RETURN: a bundle (associated sheaf to module over S), the associated sheaf to the cokernel of it is the beilinson bundle
1368EXAMPLE: example simpleBeilinsonBundle
1369"
1370{
1371  ring S = basering;
1372  def E = L[1];
1373  int t = nrows(getVariableWeights(S));
1374  bundle B;
1375  module M;
1376
1377  if ( w<1 || w>t)
1378  {
1379    return(B); // return the zero module
1380  }
1381
1382  // initialize unit vector with one in position w
1383  intvec d = (1..t) - (1..t);
1384  d[w] = 1;
1385  int j;
1386  int nw = countMultiDegree(d, getVariableWeights(S));
1387
1388  if ( a < 0 || a > nw )
1389  {
1390    return(B); // return the zero bundle
1391  }
1392
1393
1394  if ( a == 0)
1395  {
1396    M = freemodule(1);
1397    intmat gradeM[t][1];
1398    M = setModuleGrading(M,gradeM);
1399    B.m = M;
1400
1401  }
1402  else
1403  {
1404    if (a == nw +1)
1405    {
1406      M = freemodule(1);
1407      intmat gradeM[t][1]
1408      gradeM[w,1] = 1;
1409      M = setModuleGrading(M,gradeM);
1410      B.m = M;
1411    }
1412    else
1413    {
1414      setring(E);
1415      list sortedB = sortedBases(w);
1416      matrix K = koszulmap(a + 2,sortedB);
1417      setring(S);
1418      matrix K = fetch(E,K);
1419      // have to add multigrading
1420      B.iscoker = 1;
1421      M = module(K);
1422      intmat gradeM[t][nrows(M)];
1423      M = setModuleGrading(M,gradeM);
1424      B.m = twist(M,-d);   //STIMMT DAS SO WIRKLICH?
1425      }
1426  }
1427  return(B);
1428}
1429example
1430{"EXAMPLE:";
1431  echo = 2;
1432  intvec f = 2,3;
1433  def (S,E) = productOfProjectiveSpaces(f);
1434  setring(S);
1435  bundle B = simpleBeilinsonBundle(1,1,E);
1436  print(B);
1437  getModuleGrading(B.m);
1438
1439  simpleBeilinsonBundle(1,2,E);
1440}
1441
1442
1443///////////////////////////////////////////////////////////////////////////////
1444proc beilinsonBundle(intvec a, list L)
1445"USAGE:  computes a beilinson bundle (i.e. the pullback of a single projective space factor),
1446      with notation in the paper: it computes U^a
1447ASSUME:  the current basering is S, L ist list with entry E (ring);
1448    if P = P^{n_1} x....xP^{n_t}, size(a)=t and 0 <= a_i <= n_i
1449    if the inputs are not in this range, then the zero module is returned
1450NOTE:
1451RETURN: a bundle (associated sheaf to module over S), the associated sheaf to the cokernel of it is the beilinson bundle
1452EXAMPLE: example beilinsonBundle
1453"
1454{
1455  ring S = basering;
1456  int t = nrows(getVariableWeights(S));
1457  if(size(a) != t)
1458  {
1459    ERROR("Size of input vector a and number t of projective spaces are not compatible.")
1460  }
1461  int i;
1462  bundle B = simpleBeilinsonBundle(a[1],1,L);
1463  for (i =  2; i<= t; i++)
1464  {
1465    B = tensorBundle(B,simpleBeilinsonBundle(a[i],i,L));
1466  }
1467  return(B);
1468}
1469example
1470{"EXAMPLE:";
1471  echo = 2;
1472  intvec f = 2,3;
1473  def (S,E) = productOfProjectiveSpaces(f);
1474  setring(S);
1475  intvec c = 1,1;
1476  bundle B = beilinsonBundle(c,E);
1477  B;
1478
1479  bundle B1 = simpleBeilinsonBundle(1,1,E);
1480  bundle B2 = simpleBeilinsonBundle(1,2,E);
1481  bundle B3 = tensorBundle(B1,B2);
1482  B3;
1483
1484}
1485
1486
1487///////////////////////////////////////////////////////////////////////////////
1488proc printBundle(bundle B)
1489"USAGE:  prints a bundle
1490RETURN: nothing
1491"
1492{
1493  if(B.iscoker == 1)
1494  {
1495    print("coker");
1496    print(B.m);
1497  }
1498
1499  else
1500  {
1501    print(B.m)
1502  }
1503}
1504
1505
1506///////////////////////////////////////////////////////////////////////////////
1507proc tensorBundle(bundle B1, bundle B2)
1508"USAGE:  computes the tensor product of the bundles
1509RETURN: a bundle
1510EXAMPLE: example tensorBundle
1511"
1512{
1513  bundle B;
1514
1515  // first have to consider the two special cases
1516  if (B1.iscoker == 0 || B2.iscoker == 0)
1517  {
1518    if (B1.iscoker == 0)
1519    {
1520      if (B1.m == 0)
1521      {
1522        // return 0
1523        B = B1;
1524      }
1525      else
1526      {
1527        // then B1.m is just the free module of rank 1
1528        B = B2;
1529      }
1530    }
1531    else
1532    {
1533      if (B2.m == 0)
1534      {
1535        // return 0
1536        B = B2;
1537      }
1538      else
1539      {
1540        // then B2.m is just the free module of rank 1
1541        B = B1;
1542      }
1543    }
1544  }
1545  else
1546  {
1547    B.iscoker = 1;
1548    B.m = multiDegTensor(B1.m,B2.m);
1549  }
1550  return(B);
1551}
1552example
1553{"EXAMPLE:";
1554  echo = 2;
1555  intvec f = 2,3;
1556  def (S,E) = productOfProjectiveSpaces(f);
1557  setring(S);
1558  bundle B1 = simpleBeilinsonBundle(1,1,E);
1559  bundle B2 = simpleBeilinsonBundle(1,2,E);
1560
1561  bundle B3 = simpleBeilinsonBundle(1,0,E); // zero bundle
1562  bundle B4 = simpleBeilinsonBundle(0,1,E);
1563
1564  bundle B5 = tensorBundle(B1,B2);
1565  B5;
1566
1567  bundle B6 = tensorBundle(B2,B3);
1568  B6;
1569
1570  bundle B7 = tensorBundle(B2,B4);
1571  B7;
1572}
1573
1574
1575///////////////////////////////////////////////////////////////////////////////
1576proc directSumBundle(bundle B1, bundle B2)
1577"USAGE:  computes the direct sum of the bundles B1 and B2
1578RETURN: a bundle
1579EXAMPLE: example directSumBundle
1580"
1581{
1582  bundle B;
1583  module M;
1584  // first have to consider the special cases
1585  if (B1.iscoker == 0 || B2.iscoker == 0)
1586  {
1587    if (B1.iscoker == 0)
1588    {
1589      if(B1.m == 0 || B2.m == 0)
1590      {
1591        // return B2
1592        B = B2;
1593      }
1594      else
1595      {
1596        // then B1.m is just the free module of rank 1
1597        if(B2.iscoker == 0)
1598        {
1599          // both bundles are the bundles corresponding to S^1
1600          M = freemodule(2);
1601          intmat grading[2][2];
1602          M = setModuleGrading(M,grading);
1603          B.m = M;
1604        }
1605        else
1606        {
1607          // have to add zero row to B2.m
1608          matrix z[ncols(B2.m)][1];
1609          M = module(transpose(concat(z,transpose(B2.m))));
1610          intmat grading = concatIntmat(getModuleGrading(B1.m),getModuleGrading(B2.m));
1611          M = setModuleGrading(M,grading);
1612          B.iscoker = 1;
1613          B.m = M;
1614        }
1615      }
1616    }
1617    else
1618    {
1619      if (B2.m == 0)
1620      {
1621        // return B1
1622        B = B1;
1623      }
1624      else
1625      {
1626        // then B2.m is just the free module of rank 1
1627        // have to add zero row to B1.m
1628        matrix z[ncols(B1.m)][1];
1629        M = module(transpose(concat(transpose(B1.m),z)));
1630        intmat grading = concatIntmat(getModuleGrading(B1.m),getModuleGrading(B2.m));
1631        M = setModuleGrading(M,grading);
1632        B.iscoker = 1;
1633        B.m = M;
1634      }
1635    }
1636  }
1637  else
1638  {
1639    intmat grading = concatIntmat(getModuleGrading(B1.m), getModuleGrading(B2.m));
1640    // need to construct the new matrix
1641    matrix M1[nrows(B1.m)][ncols(B2.m)];
1642    matrix M2[nrows(B2.m)][ncols(B1.m)];
1643    M1 = transpose(concat(B1.m,M1));
1644    M2 = transpose(concat(M2,B2.m));
1645    M = module(transpose(concat(M1,M2)));
1646    M = setModuleGrading(M,grading);
1647    B.iscoker = 1;
1648    B.m = M;
1649  }
1650
1651  return(B);
1652}
1653example
1654{"EXAMPLE:";
1655  echo = 2;
1656  intvec f = 2,3;
1657  def (S,E) = productOfProjectiveSpaces(f);
1658  setring(S);
1659
1660  bundle B1 = simpleBeilinsonBundle(1,1,E);
1661  bundle B2 = simpleBeilinsonBundle(1,2,E);
1662  bundle B3 = simpleBeilinsonBundle(1,0,E); // zero bundle
1663  bundle B4 = simpleBeilinsonBundle(0,1,E);
1664
1665  bundle B5 = directSumBundle(B1,B2);
1666  B5;
1667
1668  bundle B6 = directSumBundle(B3,B2);
1669  B6;
1670
1671  bundle B7 = directSumBundle(B1,B4);
1672  B7;
1673}
1674
1675
1676///////////////////////////////////////////////////////////////////////////////
1677proc concatIntmat(intmat A, intmat B)
1678{
1679  if (nrows(A) != nrows(B))
1680  {
1681    nrows(A);
1682    nrows(B);
1683    ERROR("A and B do not have the same number of rows");
1684  }
1685  // return the concatenated matrix [A; B]
1686  int i,j;
1687  intmat AB[nrows(A)][ncols(A)+ncols(B)];
1688
1689  for (i = 1; i <= nrows(AB); i++)
1690  {
1691    for (j = 1; j <= ncols(AB); j++)
1692    {
1693      if(j <= ncols(A))
1694      {
1695        AB[i,j] = A[i,j];
1696      }
1697      else
1698      {
1699        AB[i,j] = B[i,j-ncols(A)];
1700      }
1701    }
1702  }
1703  return(AB)
1704}
1705
1706
1707///////////////////////////////////////////////////////////////////////////////
1708proc shift(multigradedcomplex A, int i)
1709"USAGE:  computes A[i], the shifted multigraded complex
1710RETURN: shifted multigradedcomplex
1711"
1712{
1713  A.shift = A.shift + i;
1714  if ( i%2 == 0)
1715  {
1716    return(A);
1717  }
1718  else
1719  {
1720    for (int k = 1; k<= size(A.differentials); k++)
1721    {
1722      A.differentials[k] = setModuleGrading(module(-A.differentials[k]), getModuleGrading(A.differentials[k]));
1723    }
1724    return(A);
1725  }
1726}
1727
1728
1729///////////////////////////////////////////////////////////////////////////////
1730//
1731// static procedures
1732//
1733///////////////////////////////////////////////////////////////////////////////
1734
1735
1736///////////////////////////////////////////////////////////////////////////////
1737static proc jacobM(matrix M) //kopiert aus sheafcoh.lib
1738{
1739  // computes the jacobian matrix of the input matrix
1740   int n=nvars(basering);
1741   matrix B=transpose(diff(M,var(1)));
1742   int i;
1743   for(i=2;i<=n;i++)
1744   {
1745     B=concat(B,transpose(diff(M,var(i))));
1746   }
1747   return(transpose(B));
1748}
1749
1750
1751//////////////////////////////////////////////////////////////////////////
1752static proc countMultiDegree(intvec c, intmat multiDegrees)
1753"USAGE:  counts how often a multidegree occurs in the matrix multiDegrees
1754ASSUME:  nrows(multiDegrees) == length(c);
1755RETURN:  cohomologyMatrix in ZZ[h] (klappt aber leider irgendwie nicht, wegen Ringwechsel in Funktion)
1756"
1757{
1758  // iterate through the columns of matrix multiDegrees and count how often c arises as a colum
1759  int numc;
1760  int i;
1761  for (i=1;i<=ncols(multiDegrees);i++)
1762  {
1763    if(submat(multiDegrees,1..nrows(multiDegrees),i) == c)
1764    {
1765      numc= numc +1;
1766    }
1767  }
1768  return(numc);
1769}
1770
1771
1772///////////////////////////////////////////////////////////////////////////////
1773static proc subtractIntMat(intmat A, int d)
1774{
1775  //uses subtract to subtract d from all the columns
1776  matrix result;
1777  intvec c;
1778
1779  for (int i = 1; i<= ncols(A);i++)
1780  {
1781    c = A[1,i],A[2,i];
1782    result = concat(result, matrix(subtract(c,d)));
1783  }
1784
1785  result = submat(result,1..2,2..ncols(result));
1786
1787  return(result);
1788}
1789
1790
1791///////////////////////////////////////////////////////////////////////////////
1792static proc subtract(intvec c, int d)
1793{
1794  //if size(c) != 2 then error
1795  // assume d >0
1796  //subtract in total d from the intvec c (go through all possibilities)
1797  // there are in total d+1 possibilities
1798  intmat result[2][d+1];
1799  int i = d;
1800  int j = 0;
1801  for (int k = 1; k<=d+1;k++)
1802  {
1803    result[1,k] = c[1]-i;
1804    result[2,k] = c[2]-j;
1805    i = i-1;
1806    j = j+1;
1807  }
1808  return(result)
1809}
1810
1811
1812///////////////////////////////////////////////////////////////////////////////
1813static proc matrixWithSpecificEntries(int a, int b, intvec c)
1814{
1815  // ith row has entries c[i]
1816  int i,j;
1817  intmat A[a][b];
1818  for (i =1; i<= a; i++)
1819  {
1820    for (j =1; j<= b; j++)
1821    {
1822      A[i,j] = c[i];
1823    }
1824  }
1825  return(A);
1826}
1827
1828
1829///////////////////////////////////////////////////////////////////////////////
1830static proc deleteZerosReso(list L)
1831"USAGE:  deletes all the zero entries in the list which represents a complex
1832RETURN:  list
1833NOTE:  the shift of homological degreee stored in the first entry of L has to be adjusted
1834"
1835{
1836  int i=2;
1837  int flag = 1;
1838  while (flag)
1839  {
1840
1841    if (size(L) <= 1)
1842    {
1843      // nothing more to do, list is just zero and ist just an empty complex
1844      flag = 0;
1845    }
1846
1847    else
1848    {
1849      // check whether entry is the zero module (size(L[i]) == 0)
1850      // or if the entry is the zero matrix (L[i] == 0)
1851      if (L[i] == 0 || size(L[i]) == 0)
1852      {
1853        // delete list entry
1854        L = delete(L,2);
1855        L[1] = L[1]-1;
1856      }
1857      else
1858      {
1859        flag = 0;
1860      }
1861    }
1862  }
1863
1864  int n = size(L);
1865  for (i = n; i >= 2; i--)
1866  {
1867    if (L[i] == 0 || size(L[i]) == 0)
1868    {
1869      L = delete(L,i);
1870    }
1871  }
1872  return(L);
1873}
1874
1875
1876///////////////////////////////////////////////////////////////////////////////
1877static proc deleteColumnsIntmat(intmat A, intvec c)
1878"USAGE:  delete the columns of A not corresponding to the indices in c[2],..., c[size(c)]
1879ASSUME:  first entry of c is zero and will not be considered, entries in c are in the right range
1880RETURN:   intmat with deleted columns
1881"
1882{
1883  if (size(c) == 1)
1884  {
1885    intmat C[1][1] =0;
1886    return(C);
1887  }
1888  intvec d = c[2..size(c)];
1889  intmat K[nrows(A)][size(c)-1] = A[1..nrows(A),d];
1890  return(K);
1891}
1892
1893
1894///////////////////////////////////////////////////////////////////////////////
1895static proc deleteRows(matrix A, intvec c)
1896"USAGE:  delete the rows of A not corresponding to the indices in c[2],..., c[size(c)]
1897ASSUME:  first entry of c is zero and will not be considered, entries in c are in the right range
1898RETURN:   matrix with deleted rows
1899NOTE:
1900EXAMPLE:
1901KEYWORDS:
1902"
1903{
1904  matrix B = deleteColumns(transpose(A),c);
1905  return(transpose(B));
1906}
1907
1908
1909///////////////////////////////////////////////////////////////////////////////
1910static proc deleteColumns(matrix A, intvec c)
1911"USAGE:  delete the columns of A not in c[2],..., c[size(c)]
1912ASSUME:  first entry of c is zero and will not be considered, entries in c are in the right range
1913RETURN:   matrix with deleted columns
1914NOTE:
1915EXAMPLE:
1916KEYWORDS:
1917"
1918{
1919  if (size(c) == 1)
1920  {
1921    return(matrix(0));
1922  }
1923
1924  intvec d = c[2..size(c)];
1925  A = submat(A,1..nrows(A),d);
1926  return(A);
1927}
1928
1929
1930///////////////////////////////////////////////////////////////////////////////
1931static proc goodColumns(intmat A, intvec c, intvec I, intvec J, intvec K)
1932"USAGE:  compute columns of A which have entries in the desired range
1933ASSUME:  I,J,K are disjoint subsets of {1,...,t},
1934RETURN:  intvec c which is just 0 if no column is in the desired range, otherwise first entry is
1935    zero and the other entries are the indices of columns in the desired range
1936NOTE:
1937EXAMPLE:
1938KEYWORDS:
1939"
1940{
1941  // need to filter which columns satisfy a_i < c_i for i in I
1942  // a_i = c_i for i in J, a_i >= c_i for i in K
1943  intvec d;
1944  for (int i = 1; i <= ncols(A); i++)
1945  {
1946    if (isGood(intvec(A[1..nrows(A), i]),c, I,J,K))
1947    {
1948      d = d, i;
1949    }
1950  }
1951  return(d);
1952}
1953
1954
1955///////////////////////////////////////////////////////////////////////////////
1956static proc isGood(intvec a, intvec c, intvec I, intvec J, intvec K)
1957{
1958  // return 1 if the vector a satisfies a_i < c_i for i in I
1959  // a_i = c_i for i in J, a_i >= c_i for i in K
1960  int i;
1961
1962  for (i = 2; i <= size(I); i++)
1963  {
1964     if (a[I[i]] >= c[I[i]])
1965     {
1966       return(0);
1967     }
1968  }
1969
1970  for (i = 2; i <= size(J); i++)
1971  {
1972    if (a[J[i]] != c[J[i]])
1973     {
1974       return(0);
1975     }
1976  }
1977
1978  for (i = 2; i <= size(K); i++)
1979  {
1980    if (a[K[i]] < c[K[i]])
1981     {
1982       return(0);
1983     }
1984  }
1985  return(1);
1986}
1987
1988
1989///////////////////////////////////////////////////////////////////////////////
1990static proc isDisjoint(intvec I, intvec J, intvec K)
1991"USAGE:  test whether the entries of I,J,K are disjoint (not consider 0)
1992NOTE: total dumm und aufwaendig...
1993RETURN:  1 or 0
1994"
1995{
1996  int i,j,k;
1997  for (i = 1; i <= size(I); i++)
1998  {
1999    for (j = 1; j <= size(J); j++)
2000    {
2001      for (k = 1; k <= size(K); k++)
2002      {
2003        if (I[i] != 0 && (I[i] == J[j] || I[i] == K[k]))
2004        {
2005          return(0);
2006        }
2007
2008        if (J[j] != 0 && J[j] == K[k])
2009        {
2010          return(0);
2011        }
2012      }
2013    }
2014  }
2015  return(1);
2016}
2017
2018
2019///////////////////////////////////////////////////////////////////////////////
2020static proc getColumnIntmat(intmat A, int i)
2021"USAGE:   returns intvec corresponding to ith column if the matrix
2022ASSUME:
2023RETURN: intvec
2024"
2025{
2026  intvec b = A[1,i];
2027  for (int k = 2; k<= nrows(A); k++)
2028  {
2029    b = b, A[k,i];
2030  }
2031  return(b);
2032}
2033
2034
2035///////////////////////////////////////////////////////////////////////////////
2036static proc getTargetGrading(matrix A, intmat sourceGrading)
2037"USAGE:  computes the shifts in the target of A when we regard A as a homogeneous map
2038ASSUME:  A a (homogeneous) matrix, souceGrading has represents the twists in the source when m is regarded as a mapping,
2039assume we are over a Z^2-graded ring
2040RETURN:  intmat, the shifts in the target
2041NOTE:
2042EXAMPLE: example getTargetGrading
2043KEYWORDS:
2044"
2045{
2046  // consider the map F1 = \oplus S(-d_j) \to F0 = \oplus S(-c_i)
2047  int cols = ncols(A);
2048  int rows = nrows(A);
2049  intmat targetGrading[nrows(sourceGrading)][rows];
2050
2051  // TODO : Check if sourceGrading has the right size
2052
2053  int i,j;
2054  int nonzeroentry;
2055  for (i = 1; i<= rows; i++)
2056  {
2057    nonzeroentry = 1;
2058    while(nonzeroentry <= cols )
2059    {
2060
2061      if (A[i,nonzeroentry]!= 0)
2062        {
2063        // apply formula and compute c_i
2064
2065        for (j = 1; j<= nrows(sourceGrading); j++)
2066        {
2067          targetGrading[j,i] = sourceGrading[j,nonzeroentry] - multiDeg(poly(A[i,nonzeroentry]))[j];
2068        }
2069
2070        // do the following to stop the while loop
2071        break;
2072        }
2073      nonzeroentry = nonzeroentry + 1;
2074    }
2075    if (nonzeroentry == (cols + 1))
2076    {
2077      ERROR("Matrix has a zero row.")
2078    }
2079  }
2080
2081  return(targetGrading);
2082}
2083example
2084{"EXAMPLE:";
2085   echo = 2;
2086   intvec c = 1,2;
2087   def (S,E) = productOfProjectiveSpaces(c);
2088   setring(S);
2089   matrix m[4][2] = x(0)(0), x(1)(0),x(0)(1),0,0,x(1)(1), 0,x(1)(2);
2090   print(m);
2091  intmat sourceGrading[2][2] = 1,0,0,1;
2092  getTargetGrading(m,sourceGrading);
2093}
2094
2095
2096///////////////////////////////////////////////////////////////////////////////
2097static proc getSourceGrading(matrix A, intmat targetGrading)
2098"USAGE:  computes the shifts in the target of A when we regard A as a homogeneous map
2099ASSUME:  A a (homogeneous) matrix, souceGrading has represents the twists in the source when m is regarded as a mapping,
2100assume we are over a Z^2-graded ring
2101RETURN:  intmat, the shifts in the target
2102EXAMPLE: example getSourceGrading
2103"
2104{
2105  // TODO: Eine der beiden Funktionen ist eigentlich unnoetig, kann man auch auf die andere zurueckfuehren
2106
2107  // consider the map F1 = \oplus S(-d_j) \to F0 = \oplus S(-c_i)
2108  int cols = ncols(A);
2109  int rows = nrows(A);
2110  intmat sourceGrading[2][cols];
2111
2112  // TODO : Check if targetGrading has the right size
2113
2114  int i;
2115  int nonzeroentry;
2116  for (i = 1; i<= cols; i++)
2117  {
2118    nonzeroentry = 1;
2119    while(nonzeroentry <= rows )
2120    {
2121
2122      if (A[nonzeroentry,i]!= 0)
2123        {
2124          // apply formula and compute c_i
2125          sourceGrading[1,i] = targetGrading[1,nonzeroentry] + multiDeg(poly(A[nonzeroentry,i]))[1];
2126          sourceGrading[2,i] = targetGrading[2,nonzeroentry] + multiDeg(poly(A[nonzeroentry,i]))[2];
2127
2128          // in this case stop the while loop
2129          break;
2130        }
2131      nonzeroentry = nonzeroentry + 1;
2132    }
2133    if (nonzeroentry == (rows + 1))
2134    {
2135      ERROR("Matrix has a zero column.")
2136    }
2137  }
2138  return(sourceGrading);
2139}
2140example
2141{"EXAMPLE:";
2142  echo = 2;
2143  intvec c = 1,2;
2144  def (S,E) = productOfProjectiveSpaces(c);
2145  setring(S);
2146  matrix m[4][2] = x(0)(0), x(1)(0),x(0)(1),0,0,x(1)(1), 0,x(1)(2);
2147  print(m);
2148  intmat targetGrading[2][4] = 0,0,0,0,0,0,0,0;
2149  getSourceGrading(m,targetGrading);
2150}
2151
2152
2153///////////////////////////////////////////////////////////////////////////////
2154static proc isLEQ(intvec c, intvec d)
2155"USAGE:  checks whether the intvec c is lower or equal to the intvec d (componentwise)
2156RETURN:  int 1 if c <= d, otherwise return 0
2157EXAMPLE: example isLEQ
2158"
2159{
2160  if (size(c) != size(d))
2161  {
2162    ERROR("The input vectors need to have the same size.")
2163  }
2164
2165  for (int i = 1; i<= size(c); i++)
2166  {
2167    if (c[i] > d[i])
2168    {
2169      return(0);
2170    }
2171  }
2172  return(1);
2173}
2174example
2175{"EXAMPLE:";
2176  echo = 2;
2177  ring R = 0,x,dp;
2178  intvec c1 = 3,4;
2179  intvec c2 = 5,5;
2180  intvec c3 = 6,7,8;
2181  isLEQ(c1,c2);
2182  isLEQ(c2,c1);
2183  isLEQ(c1,c1);
2184  isLEQ(c1,c3);
2185}
2186
2187
2188///////////////////////////////////////////////////////////////////////////////
2189static proc isSmaller(intvec c, intvec d)
2190"USAGE:  isSmaller(c,d); c intvec, d intvec
2191ASSUME:  c and d are integer vectors
2192RETURN:  int 1 if c < d, otherwise return 0
2193EXAMPLE: example isLEQ
2194"
2195{
2196  if (size(c) != size(d))
2197  {
2198    ERROR("The input vectors need to have the same size.")
2199  }
2200
2201  for (int i = 1; i<= size(c); i++)
2202  {
2203    if (c[i] >= d[i])
2204    {
2205      return(0);
2206    }
2207  }
2208  return(1);
2209}
2210example
2211{"EXAMPLE:";
2212  echo = 2;
2213  ring R = 0,x,dp;
2214  intvec c1 = 3,4;
2215  intvec c2 = 5,5;
2216  intvec c3 = 6,7,8;
2217  isLEQ(c1,c2);
2218  isLEQ(c2,c1);
2219  isLEQ(c1,c1);
2220  isLEQ(c1,c3);
2221}
2222
2223
2224///////////////////////////////////////////////////////////////////////////////
2225static proc vectorsLEQ(intvec c)
2226"USAGE:  compute all vectors >= 0 and <= c
2227ASSUME:  c has nonnegative entries
2228RETURN:  intmat A where the columns represent all the vectors which are <= c, >= 0
2229EXAMPLE: example vectorsLEQ
2230"
2231{
2232  int i,j,k,numcolumns;
2233  matrix A[size(c)][1];
2234  matrix v[size(c)][1];
2235  for (i = 1; i<= size(c); i++)
2236  {
2237    numcolumns = ncols(A);
2238    for(j = 1; j<= numcolumns; j++)
2239    {
2240      for (k = 1; k <= c[i]; k++)
2241      {
2242        v = v-v;
2243        v[i,1] = k;
2244        A = concat(A,v+submat(A,1..nrows(A),j));
2245      }
2246    }
2247  }
2248
2249  return(A);
2250  //lowerbounds = concat(lowerbounds, matrix(getModuleGrading(T[i])));
2251}
2252example
2253{"EXAMPLE:";
2254  echo = 2;
2255  ring R = 0,x,dp;
2256  intvec c = 1,2,3;
2257  matrix A = vectorsLEQ(c);
2258  print(A);
2259}
2260
2261
2262///////////////////////////////////////////////////////////////////////////////
2263static proc inBeilinsonWindow(intmat D, intvec n)
2264"USAGE:  compute the indices of all multidegrees in D in the range 0 \leq a \leq n
2265RETURN:  intvec c where the entries represent the indices of multidegrees in the range,
2266    the first entry is always 0, outputs the zero vector if all multidegrees are not in desired range.
2267EXAMPLE: example inBeilinsonWindow
2268"
2269{
2270  if (nrows(D) != size(n))
2271  {
2272    ERROR("The number of columns and size of n have to be equal.")
2273  }
2274
2275  intvec c;
2276  intvec zero = n-n;
2277  int i,j;
2278  int rows = nrows(D);
2279  intvec dcol = n;
2280  for (i = 1; i <= ncols(D); i++)
2281  {
2282    for(j = 1; j<= rows; j++)
2283    {
2284      dcol[j] = D[j,i];
2285    }
2286    if(isLEQ(dcol,zero) && isLEQ(-n,dcol))
2287    {
2288      c = c,i;
2289    }
2290  }
2291  return(c);
2292}
2293example
2294{"EXAMPLE:";
2295  echo = 2;
2296  ring R = 0,x,dp;
2297  intvec n = 1,2,3;
2298  intmat D[3][5] = 1,1,0,6,1,2,3,1,0,0,3,2,4,5,0;
2299  print(D);
2300  intvec c = inBeilinsonWindow(D,n);
2301  print(c);
2302}
2303
2304
2305///////////////////////////////////////////////////////////////////////////////
2306static proc deleteZerosMultigradedComplex(multigradedcomplex T)
2307"USAGE:  delete superflous zeros in a multigraded complex
2308RETURN:  multigradedcomplex with deleted zeros
2309"
2310{
2311  int nmods = size(T.modules);
2312  int nonzeros;
2313  int flag = 1;
2314  int i = nmods-1;
2315  while(flag && i>0)
2316  {
2317    if (size(T.modules[i]) == 0 && size(T.modules[i+1]) == 0)
2318    {
2319      T.modules = delete(T.modules,i+1);
2320      T.differentials = delete(T.differentials,i);
2321    }
2322    else
2323    {
2324      if (size(T.modules[i]) != 0 && size(T.modules[i+1]) == 0)
2325      {
2326        T.differentials[i] = module(matrix(0));
2327        flag = 0;
2328      }
2329      else
2330      {
2331        flag = 0;
2332      }
2333    }
2334    i = i-1;
2335  }
2336
2337  flag = 1;
2338  while(flag && (size(T.modules) >= 2))
2339  {
2340    if (size(T.modules[1]) == 0 && size(T.modules[2]) == 0)
2341    {
2342      T.modules = delete(T.modules,1);
2343      T.differentials = delete(T.differentials,1);
2344      T.shift = T.shift -1;
2345    }
2346    else
2347    {
2348      if (size(T.modules[1]) == 0 && size(T.modules[2]) != 0)
2349      {
2350        T.differentials[1] = module(matrix(0));
2351        flag = 0;
2352      }
2353      else
2354      {
2355        flag = 0;
2356      }
2357    }
2358  }
2359
2360  if (size(T.modules) == 0)
2361  {
2362    T.modules = list();
2363    T.differentials = list();
2364    T.shift = 0;
2365  }
2366  return(T);
2367}
2368
2369
2370///////////////////////////////////////////////////////////////////////////////
2371static proc getDimensionVector(intmat variableWeights)
2372"USAGE:  compute the indices of all multidegrees in D in the range 0 \leq a \leq n
2373RETURN:  intvec n
2374"
2375{
2376  int i;
2377  intvec n = 1..nrows(variableWeights);
2378  intvec b;
2379  int j = 1;
2380  for (i=1; i<= nrows(variableWeights); i++)
2381  {
2382    b = intvec(variableWeights[1..nrows(variableWeights), j]);
2383    n[i] = countMultiDegree(b,variableWeights);
2384    j = j + n[i];
2385    n[i] = n[i]-1;
2386  }
2387  return(n);
2388}
2389
2390
2391///////////////////////////////////////////////////////////////////////////////
2392static proc gradingAndVectorCompatible(module M, intvec c)
2393{
2394  if(nrows(getModuleGrading(M)) == size(c))
2395  {
2396    return(1);
2397  }
2398  else
2399  {
2400    return(0);
2401  }
2402}
2403
2404
2405///////////////////////////////////////////////////////////////////////////////
2406static proc deleteFirstEntry(multigradedcomplex tate)
2407{
2408  tate.modules = delete(tate.modules,1);
2409  tate.differentials = delete(tate.differentials,1);
2410  return(tate);
2411}
2412
Note: See TracBrowser for help on using the repository browser.