source: git/Singular/LIB/reszeta.lib @ 0dd77c2

spielwiese
Last change on this file since 0dd77c2 was 341696, checked in by Hans Schönemann <hannes@…>, 14 years ago
Adding Id property to all files git-svn-id: file:///usr/local/Singular/svn/trunk@12231 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 161.6 KB
Line 
1//////////////////////////////////////////////////////////////////////////////
2version="$Id$";
3category="Commutative Algebra";
4info="
5LIBRARY:  reszeta.lib       topological Zeta-function and
6                            some other applications of desingularization
7
8AUTHORS:  A. Fruehbis-Krueger,  anne@mathematik.uni-kl.de,
9@*        G. Pfister,           pfister@mathematik.uni-kl.de
10
11MAIN PROCEDURES:
12intersectionDiv(L)   computes intersection form and genera of exceptional
13                     divisors (isolated singularities of surfaces)
14spectralNeg(L)       computes negative spectral numbers
15                     (isolated hypersurface singularity)
16discrepancy(L)       computes discrepancy of given resolution
17zetaDL(L,d)          computes Denef-Loeser zeta function
18                     (hypersurface singularity of dimension 2)
19
20AUXILLIARY PROCEDURES:
21collectDiv(L[,iv])   identify exceptional divisors in different charts
22                     (embedded and non-embedded case)
23prepEmbDiv(L[,b])    prepare list of divisors (including components
24                     of strict transform, embedded case)
25abstractR(L)         pass from embedded to non-embedded resolution
26";
27LIB "resolve.lib";
28LIB "solve.lib";
29LIB "normal.lib";
30///////////////////////////////////////////////////////////////////////////////
31static
32proc spectral1(poly h,list re, list DL,intvec v, intvec n)
33"Internal procedure - no help and no example available
34"
35{
36//--- compute one spectral number
37//--- DL is output of prepEmbDiv
38   int i;
39   intvec w=computeH(h,re,DL);
40   number gw=number(w[1]+v[1])/number(n[1]);
41   for(i=2;i<=size(v);i++)
42   {
43      if(gw>number(w[i]+v[i])/number(n[i]))
44      {
45         gw=number(w[i]+v[i])/number(n[i]);
46      }
47   }
48   return(gw-1);
49}
50
51///////////////////////////////////////////////////////////////////////////////
52
53proc spectralNeg(list re,list #)
54"USAGE:   spectralNeg(L);
55@*        L = list of rings
56ASSUME:   L is output of resolution of singularities
57RETURN:   list of numbers, each a spectral number in (-1,0]
58EXAMPLE:  example spectralNeg;  shows an example
59"
60{
61//-----------------------------------------------------------------------------
62// Initialization and Sanity Checks
63//-----------------------------------------------------------------------------
64   int i,j,l;
65   number bound;
66   list resu;
67   if(size(#)>0)
68   {
69//--- undocumented feature:
70//--- if # is not empty it computes numbers up to this bound,
71//--- not necessarily spectral numbers
72      bound=number(#[1]);
73   }
74//--- get list of embedded divisors
75   list DL=prepEmbDiv(re,1);
76   int k=1;
77   ideal I,delI;
78   number g;
79   int m=nvars(basering);
80//--- prepare the multiplicities of exceptional divisors N and nu
81   intvec v=computeV(re,DL);        // nu
82   intvec n=computeN(re,DL);        // N
83//---------------------------------------------------------------------------
84// start computation, first case separately, then loop
85//---------------------------------------------------------------------------
86   resu[1]=spectral1(1,re,DL,v,n);  // first number, corresponding to
87                                    // volume form itself
88   if(resu[1]>=bound)
89   {
90//--- exceeds bound ==> not a spectral number
91      resu=delete(resu,1);
92      return(resu);
93   }
94   delI=std(ideal(0));
95   while(k)
96   {
97//--- now run through all monomial x volume form, degree by degree
98      j++;
99      k=0;
100      I=maxideal(j);
101      I=reduce(I,delI);
102      for(i=1;i<=size(I);i++)
103      {
104//--- all monomials in degree j
105         g=spectral1(I[i],re,DL,v,n);
106         if(g<bound)
107         {
108//--- otherwise g exceeds bound ==> not a spectral number
109            k=1;
110            l=1;
111            while(resu[l]<g)
112            {
113               l++;
114               if(l==size(resu)+1){break;}
115            }
116            if(l==size(resu)+1){resu[size(resu)+1]=g;}
117            if(resu[l]!=g){resu=insert(resu,g,l-1);}
118         }
119         else
120         {
121            delI[size(delI)+1]=I[i];
122         }
123      }
124      attrib(delI,"isSB",1);
125   }
126   return(resu);
127}
128example
129{"EXAMPLE:";
130   echo = 2;
131   ring R=0,(x,y,z),dp;
132   ideal I=x3+y4+z5;
133   list L=resolve(I,"K");
134   spectralNeg(L);
135   LIB"gaussman.lib";
136   ring r=0,(x,y,z),ds;
137   poly f=x3+y4+z5;
138   spectrum(f);
139}
140
141///////////////////////////////////////////////////////////////////////////////
142static
143proc ordE(ideal J,ideal E,ideal W)
144"Internal procedure - no help and no example available
145"
146{
147//--- compute multiplicity of E in J -- embedded in W
148   int s;
149   if(size(J)==0){~;ERROR("ordE: J=0");}
150   ideal Estd=std(E+W);
151   ideal Epow=1;
152   ideal Jquot=1;
153   while(size(reduce(Jquot,Estd))!=0)
154   {
155      s++;
156      Epow=Epow*E;
157      Jquot=quotient(Epow+W,J);
158   }
159   return(s-1);
160}
161
162///////////////////////////////////////////////////////////////////////////////
163static
164proc computeV(list re, list DL)
165"Internal procedure - no help and no example available
166"
167{
168//--- computes for every divisor E_i its multiplicity + 1 in pi^*(w)
169//--- w a non-vanishing 1-form
170//--- note: DL is output of prepEmbDiv
171
172//-----------------------------------------------------------------------------
173// Initialization
174//-----------------------------------------------------------------------------
175   def R=basering;
176   int i,j,k,n;
177   intvec v,w;
178   list iden=DL;
179   v[size(iden)]=0;
180
181//----------------------------------------------------------------------------
182// Run through all exceptional divisors
183//----------------------------------------------------------------------------
184   for(k=1;k<=size(iden);k++)
185   {
186      for(i=1;i<=size(iden[k]);i++)
187      {
188         if(defined(S)){kill S;}
189         def S=re[2][iden[k][i][1]];
190         setring S;
191         if((!v[k])&&(defined(EList)))
192         {
193            if(defined(II)){kill II;}
194//--- we might be embedded in a non-trivial BO[1]
195//--- take this into account when forming the jacobi-determinant
196            ideal II=jacobDet(BO[5],BO[1]);
197            if(size(II)!=0)
198            {
199                v[k]=ordE(II,EList[iden[k][i][2]],BO[1])+1;
200            }
201         }
202         setring R;
203      }
204   }
205   return(v);
206}
207example
208{"EXAMPLE:";
209   echo = 2;
210   ring R=0,(x,y,z),dp;
211   ideal I=(x-y)*(x-z)*(y-z)-z4;
212   list re=resolve(I,1);
213   intvec v=computeV(re);
214   v;
215}
216
217///////////////////////////////////////////////////////////////////////////////
218static
219proc jacobDet(ideal I, ideal J)
220"Internal procedure - no help and no example available
221"
222{
223//--- Returns the Jacobian determinant of the morphism
224//--- K[x_1,...,x_m]--->K[y_1,...,y_n]/J defined by x_i ---> I_i.
225//--- Let basering=K[y_1,...,y_n], l=n-dim(basering/J),
226//--- I=<I_1,...,I_m>, J=<J_1,...,J_r>
227//--- For each subset v in {1,...,n} of l elements and
228//--- w in {1,...,r} of l elements
229//--- let K_v,w be the ideal generated by the n-l-minors of the matrix
230//--- (diff(I_i,y_j)+
231//---  \sum_k diff(I_i,y_v[k])*diff(J_w[k],y_j))_{j not in v  multiplied with
232//---                                 the determinant of (diff(J_w[i],y_v[j]))
233//--- the sum of all such ideals K_v,w plus J is returned.
234
235//----------------------------------------------------------------------------
236// Initialization
237//----------------------------------------------------------------------------
238   int n=nvars(basering);
239   int i,j,k;
240   intvec u,v,w,x;
241   matrix MI[ncols(I)][n]=jacob(I);
242   matrix N=unitmat(n);
243   matrix L;
244   ideal K=J;
245   if(size(J)==0)
246   {
247      K=minor(MI,n);
248   }
249
250//---------------------------------------------------------------------------
251// Do calculation as described above.
252// separately for case size(J)=1
253//---------------------------------------------------------------------------
254   if(size(J)==1)
255   {
256      matrix MJ[ncols(J)][n]=jacob(J);
257      N=concat(N,transpose(MJ));
258      v=1..n;
259      for(i=1;i<=n;i++)
260      {
261         L=transpose(permcol(N,i,n+1));
262         if(i==1){w=2..n;}
263         if(i==n){w=1..n-1;}
264         if((i!=1)&&(i!=n)){w=1..i-1,i+1..n;}
265         L=submat(L,v,w);
266         L=MI*L;
267         K=K+minor(L,n-1)*MJ[1,i];
268      }
269   }
270   if(size(J)>1)
271   {
272      matrix MJ[ncols(J)][n]=jacob(J);
273      matrix SMJ;
274      N=concat(N,transpose(MJ));
275      ideal Jstd=std(J);
276      int l=n-dim(Jstd);
277      int r=ncols(J);
278      list L1=indexSet(n,l);
279      list L2=indexSet(r,l);
280      for(i=1;i<=size(L1);i++)
281      {
282         for(j=1;j<=size(L2);j++)
283         {
284            for(k=1;k<=size(L1[i]);k++)
285            {
286               if(L1[i][k]){v[size(v)+1]=k;}
287            }
288            v=v[2..size(v)];
289            for(k=1;k<=size(L2[j]);k++)
290            {
291               if(L2[j][k]){w[size(w)+1]=k;}
292            }
293            w=w[2..size(w)];
294            SMJ=submat(MJ,w,v);
295            L=N;
296            for(k=1;k<=l;k++)
297            {
298               L=permcol(L,v[k],n+w[k]);
299            }
300            u=1..n;
301            x=1..n;
302            v=sort(v)[1];
303            for(k=l;k>=1;k--)
304            {
305               if(v[k])
306               {
307                  u=deleteInt(u,v[k],1);
308               }
309            }
310            L=transpose(submat(L,u,x));
311            L=MI*L;
312            K=K+minor(L,n-l)*det(SMJ);
313         }
314      }
315   }
316   return(K);
317}
318
319///////////////////////////////////////////////////////////////////////////////
320static
321proc computeH(ideal h,list re,list DL)
322"Internal procedure - no help and no example available
323"
324{
325//--- additional procedure to computeV, allows
326//--- computation for polynomial x volume form
327//--- by computing the contribution of the polynomial h
328//--- Note: DL is output of prepEmbDiv
329
330//----------------------------------------------------------------------------
331// Initialization
332//----------------------------------------------------------------------------
333   def R=basering;
334   ideal II=h;
335   list iden=DL;
336   def T=re[2][1];
337   setring T;
338   int i,k;
339   intvec v;
340   v[size(iden)]=0;
341   if(deg(II[1])==0){return(v);}
342//----------------------------------------------------------------------------
343// Run through all exceptional divisors
344//----------------------------------------------------------------------------
345   for(k=1;k<=size(iden);k++)
346   {
347      for(i=1;i<=size(iden[k]);i++)
348      {
349         if(defined(S)){kill S;}
350         def S=re[2][iden[k][i][1]];
351         setring S;
352         if((!v[k])&&(defined(EList)))
353         {
354            if(defined(JJ)){kill JJ;}
355            if(defined(phi)){kill phi;}
356            map phi=T,BO[5];
357            ideal JJ=phi(II);
358            if(size(JJ)!=0)
359            {
360               v[k]=ordE(JJ,EList[iden[k][i][2]],BO[1]);
361            }
362         }
363         setring R;
364      }
365   }
366   return(v);
367}
368
369//////////////////////////////////////////////////////////////////////////////
370static
371proc computeN(list re,list DL)
372"Internal procedure - no help and no example available
373"
374{
375//--- computes for every (Q-irred.) divisor E_i its multiplicity in f \circ pi
376//--- DL is output of prepEmbDiv
377
378//----------------------------------------------------------------------------
379// Initialization
380//----------------------------------------------------------------------------
381   def R=basering;
382   list iden=DL;
383   def T=re[2][1];
384   setring T;
385   ideal J=BO[2];
386   int i,k;
387   intvec v;
388   v[size(iden)]=0;
389//----------------------------------------------------------------------------
390// Run through all exceptional divisors
391//----------------------------------------------------------------------------
392   for(k=1;k<=size(iden);k++)
393   {
394      for(i=1;i<=size(iden[k]);i++)
395      {
396         if(defined(S)){kill S;}
397         def S=re[2][iden[k][i][1]];
398         setring S;
399         if((!v[k])&&(defined(EList)))
400         {
401            if(defined(II)){kill II;}
402            if(defined(phi)){kill phi;}
403            map phi=T,BO[5];
404            ideal II=phi(J);
405            if(size(II)!=0)
406            {
407               v[k]=ordE(II,EList[iden[k][i][2]],BO[1]);
408            }
409         }
410         setring R;
411      }
412   }
413   return(v);
414}
415example
416{"EXAMPLE:";
417   echo = 2;
418   ring R=0,(x,y,z),dp;
419   ideal I=(x-y)*(x-z)*(y-z)-z4;
420   list re=resolve(I,1);
421   intvec v=computeN(re);
422   v;
423}
424//////////////////////////////////////////////////////////////////////////////
425static
426proc countEijk(list re,list iden,intvec iv,list #)
427"Internal procedure - no help and no example available
428"
429{
430//--- count the number of points in the intersection of 3 exceptional
431//--- hyperplanes (of dimension 2) - one of them is allowed to be a component
432//--- of the strict transform
433
434//----------------------------------------------------------------------------
435// Initialization
436//----------------------------------------------------------------------------
437   int i,j,k,comPa,numPts,localCase;
438   intvec ituple,jtuple,ktuple;
439   list chList,tmpList;
440   def R=basering;
441   if(size(#)>0)
442   {
443      if(string(#[1])=="local")
444      {
445         localCase=1;
446      }
447   }
448//----------------------------------------------------------------------------
449// Find common charts
450//----------------------------------------------------------------------------
451   for(i=1;i<=size(iden[iv[1]]);i++)
452   {
453//--- find common charts - only for final charts
454      if(defined(S)) {kill S;}
455      def S=re[2][iden[iv[1]][i][1]];
456      setring S;
457      if(!defined(EList))
458      {
459        i++;
460        setring R;
461        continue;
462      }
463      setring R;
464      kill ituple,jtuple,ktuple;
465      intvec ituple=iden[iv[1]][i];
466      intvec jtuple=findInIVList(1,ituple[1],iden[iv[2]]);
467      intvec ktuple=findInIVList(1,ituple[1],iden[iv[3]]);
468      if((size(jtuple)!=1)&&(size(ktuple)!=1))
469      {
470//--- chList contains all information about the common charts,
471//--- each entry represents a chart and contains three intvecs from iden
472//--- one for each E_l
473        kill tmpList;
474        list tmpList=ituple,jtuple,ktuple;
475        chList[size(chList)+1]=tmpList;
476        i++;
477        if(i<=size(iden[iv[1]]))
478        {
479           continue;
480        }
481        else
482        {
483           break;
484        }
485      }
486   }
487   if(size(chList)==0)
488   {
489//--- no common chart !!!
490     return(int(0));
491   }
492//----------------------------------------------------------------------------
493// Count points in common charts
494//----------------------------------------------------------------------------
495   for(i=1;i<=size(chList);i++)
496   {
497//--- run through all common charts
498      if(defined(S)) { kill S;}
499      def S=re[2][chList[i][1][1]];
500      setring S;
501//--- intersection in this chart
502      if(defined(interId)){kill interId;}
503      if(localCase==1)
504      {
505//--- in this case we need to intersect with \pi^-1(0)
506         ideal interId=EList[chList[i][1][2]]+EList[chList[i][2][2]]
507                                          +EList[chList[i][3][2]]+BO[5];
508      }
509      else
510      {
511         ideal interId=EList[chList[i][1][2]]+EList[chList[i][2][2]]
512                                          +EList[chList[i][3][2]];
513      }
514      interId=std(interId);
515      if(defined(otherId)) {kill otherId;}
516      ideal otherId=1;
517      for(j=1;j<i;j++)
518      {
519//--- run through the previously computed ones
520        if(defined(opath)){kill opath;}
521        def opath=imap(re[2][chList[j][1][1]],path);
522        comPa=1;
523        while(opath[1,comPa]==path[1,comPa])
524        {
525           comPa++;
526           if((comPa>ncols(path))||(comPa>ncols(opath))) break;
527        }
528        comPa=int(leadcoef(path[1,comPa-1]));
529        otherId=otherId+interId;
530        otherId=intersect(otherId,
531                     fetchInTree(re,chList[j][1][1],
532                                 comPa,chList[i][1][1],"interId",iden));
533      }
534      otherId=std(otherId);
535//--- do not count each point more than once
536      interId=sat(interId,otherId)[1];
537      export(interId);
538      if(dim(interId)>0)
539      {
540         ERROR("CountEijk: intersection not zerodimensional");
541      }
542//--- add the remaining number of points to the total point count numPts
543      numPts=numPts+vdim(interId);
544   }
545   return(numPts);
546}
547//////////////////////////////////////////////////////////////////////////////
548static
549proc chiEij(list re, list iden, intvec iv)
550"Internal procedure - no help and no example available
551"
552{
553//!!! Copy of chiEij_local adjusted for non-local case
554//!!! changes must be made in both copies
555
556//--- compute the Euler characteristic of the intersection
557//--- curve of two exceptional hypersurfaces (of dimension 2)
558//--- one of which is allowed to be a component of the strict transform
559//--- using the formula chi(Eij)=2-2g(Eij)
560
561//----------------------------------------------------------------------------
562// Initialization
563//----------------------------------------------------------------------------
564  int i,j,k,chi,g;
565  intvec ituple,jtuple,inters;
566  def R=basering;
567//----------------------------------------------------------------------------
568// Find a common chart in which they intersect
569//----------------------------------------------------------------------------
570  for(i=1;i<=size(iden[iv[1]]);i++)
571  {
572//--- find a common chart in which they intersect: only for final charts
573     if(defined(S)) {kill S;}
574     def S=re[2][iden[iv[1]][i][1]];
575     setring S;
576     if(!defined(EList))
577     {
578       i++;
579       setring R;
580       continue;
581     }
582     setring R;
583     kill ituple,jtuple;
584     intvec ituple=iden[iv[1]][i];
585     intvec jtuple=findInIVList(1,ituple[1],iden[iv[2]]);
586     if(size(jtuple)==1)
587     {
588       if(i<size(iden[iv[1]]))
589       {
590//--- not in this chart
591         i++;
592         continue;
593       }
594       else
595       {
596         if(size(inters)==1)
597         {
598//--- E_i and E_j do not meet at all
599            return("leer");
600         }
601         else
602         {
603            return(chi);
604         }
605       }
606     }
607//----------------------------------------------------------------------------
608// Run through common charts and compute the Euler characteristic of
609// each component of Eij.
610// As soon as a component has been treated in a chart, it will not be used in
611// any subsequent charts.
612//----------------------------------------------------------------------------
613     if(defined(S)) {kill S;}
614     def S=re[2][ituple[1]];
615     setring S;
616//--- interId: now all components in this chart,
617//---          but we want only new components
618     if(defined(interId)){kill interId;}
619     ideal interId=EList[ituple[2]]+EList[jtuple[2]];
620     interId=std(interId);
621//--- doneId: already considered components
622     if(defined(doneId)){kill doneId;}
623     ideal doneId=1;
624     for(j=2;j<=size(inters);j++)
625     {
626//--- fetch the components which have already been dealt with via fetchInTree
627        if(defined(opath)) {kill opath;}
628        def opath=imap(re[2][inters[j]],path);
629        k=1;
630        while((k<ncols(opath))&&(k<ncols(path)))
631        {
632           if(path[1,k+1]!=opath[1,k+1]) break;
633           k++;
634        }
635        if(defined(comPa)) {kill comPa;}
636        int comPa=int(leadcoef(path[1,k]));
637        if(defined(tempId)){kill tempId;}
638        ideal tempId=fetchInTree(re,inters[j],comPa,
639                                    iden[iv[1]][i][1],"interId",iden);
640        doneId=intersect(doneId,tempId);
641        kill tempId;
642     }
643//--- only consider new components in interId
644     interId=sat(interId,doneId)[1];
645     if(dim(interId)>1)
646     {
647       ERROR("genus_Eij: higher dimensional intersection");
648     }
649     if(dim(interId)>=0)
650     {
651//--- save the index of the current chart for future use
652        export(interId);
653        inters[size(inters)+1]=iden[iv[1]][i][1];
654     }
655     BO[1]=std(BO[1]);
656     if(((dim(interId)<=0)&&(dim(BO[1])>2))||
657        ((dim(interId)<0)&&(dim(BO[1])==2)))
658     {
659       if(i<size(iden[iv[1]]))
660       {
661//--- not in this chart
662         setring R;
663         i++;
664         continue;
665       }
666       else
667       {
668         if(size(inters)==1)
669         {
670//--- E_i and E_j do not meet at all
671            return("leer");
672         }
673         else
674         {
675            return(chi);
676         }
677       }
678     }
679     g=genus(interId);
680
681//--- chi is the Euler characteristic of the (disjoint !!!) union of the
682//--- considered components
683//--- remark: components are disjoint, because the E_i are normal crossing!!!
684
685     chi=chi+(2-2*g);
686  }
687  return(chi);
688}
689//////////////////////////////////////////////////////////////////////////////
690//////////////////////////////////////////////////////////////////////////////
691static
692proc chiEij_local(list re, list iden, intvec iv)
693"Internal procedure - no help and no example available
694"
695{
696//!!! Copy of chiEij adjusted for local case
697//!!! changes must be made in both copies
698
699//--- we have to consider two different cases:
700//--- case1: E_i \cap E_j \cap \pi^-1(0) is a curve
701//---    compute the Euler characteristic of the intersection
702//---    curve of two exceptional hypersurfaces (of dimension 2)
703//---    one of which is allowed to be a component of the strict transform
704//---    using the formula chi(Eij)=2-2g(Eij)
705//--- case2: E_i \cap E_j \cap \pi^-1(0) is a set of points
706//---    count the points
707
708//----------------------------------------------------------------------------
709// Initialization
710//----------------------------------------------------------------------------
711  int i,j,k,chi,g,points;
712  intvec ituple,jtuple,inters;
713  def R=basering;
714//----------------------------------------------------------------------------
715// Find a common chart in which they intersect
716//----------------------------------------------------------------------------
717  for(i=1;i<=size(iden[iv[1]]);i++)
718  {
719//--- find a common chart in which they intersect: only for final charts
720     if(defined(S)) {kill S;}
721     def S=re[2][iden[iv[1]][i][1]];
722     setring S;
723     if(!defined(EList))
724     {
725       i++;
726       setring R;
727       continue;
728     }
729     setring R;
730     kill ituple,jtuple;
731     intvec ituple=iden[iv[1]][i];
732     intvec jtuple=findInIVList(1,ituple[1],iden[iv[2]]);
733     if(size(jtuple)==1)
734     {
735       if(i<size(iden[iv[1]]))
736       {
737//--- not in this chart
738         i++;
739         continue;
740       }
741       else
742       {
743         if(size(inters)==1)
744         {
745//--- E_i and E_j do not meet at all
746            return("leer");
747         }
748         else
749         {
750            return(chi);
751         }
752       }
753     }
754//----------------------------------------------------------------------------
755// Run through common charts and compute the Euler characteristic of
756// each component of Eij.
757// As soon as a component has been treated in a chart, it will not be used in
758// any subsequent charts.
759//----------------------------------------------------------------------------
760     if(defined(S)) {kill S;}
761     def S=re[2][ituple[1]];
762     setring S;
763//--- interId: now all components in this chart,
764//---          but we want only new components
765     if(defined(interId)){kill interId;}
766     ideal interId=EList[ituple[2]]+EList[jtuple[2]]+BO[5];
767     interId=std(interId);
768//--- doneId: already considered components
769     if(defined(doneId)){kill doneId;}
770     ideal doneId=1;
771     for(j=2;j<=size(inters);j++)
772     {
773//--- fetch the components which have already been dealt with via fetchInTree
774        if(defined(opath)) {kill opath;}
775        def opath=imap(re[2][inters[j]],path);
776        k=1;
777        while((k<ncols(opath))&&(k<ncols(path)))
778        {
779           if(path[1,k+1]!=opath[1,k+1]) break;
780           k++;
781        }
782        if(defined(comPa)) {kill comPa;}
783        int comPa=int(leadcoef(path[1,k]));
784        if(defined(tempId)){kill tempId;}
785        ideal tempId=fetchInTree(re,inters[j],comPa,
786                                    iden[iv[1]][i][1],"interId",iden);
787        doneId=intersect(doneId,tempId);
788        kill tempId;
789     }
790//--- only consider new components in interId
791     interId=sat(interId,doneId)[1];
792     if(dim(interId)>1)
793     {
794       ERROR("genus_Eij: higher dimensional intersection");
795     }
796     if(dim(interId)>=0)
797     {
798//--- save the index of the current chart for future use
799        export(interId);
800        inters[size(inters)+1]=iden[iv[1]][i][1];
801     }
802     BO[1]=std(BO[1]);
803     if(dim(interId)<0)
804     {
805       if(i<size(iden[iv[1]]))
806       {
807//--- not in this chart
808         setring R;
809         i++;
810         continue;
811       }
812       else
813       {
814         if(size(inters)==1)
815         {
816//--- E_i and E_j do not meet at all
817            return("leer");
818         }
819         else
820         {
821            return(chi);
822         }
823       }
824     }
825     if((dim(interId)==0)&&(dim(std(BO[1]))>2))
826     {
827//--- for sets of points the Euler characteristic is just
828//--- the number of points
829//--- fat points are impossible, since everything is smooth and n.c.
830        chi=chi+vdim(interId);
831        points=1;
832     }
833     else
834     {
835        if(points==1)
836        {
837           ERROR("components of intersection do not have same dimension");
838        }
839        g=genus(interId);
840//--- chi is the Euler characteristic of the (disjoint !!!) union of the
841//--- considered components
842//--- remark: components are disjoint, because the E_i are normal crossing!!!
843        chi=chi+(2-2*g);
844     }
845  }
846  return(chi);
847}
848//////////////////////////////////////////////////////////////////////////////
849static
850proc computeChiE(list re, list iden)
851"Internal procedure - no help and no example available
852"
853{
854//--- compute the Euler characteristic of the exceptional hypersurfaces
855//--- (of dimension 2), not considering the components of the strict
856//--- transform
857
858//----------------------------------------------------------------------------
859// Initialization
860//----------------------------------------------------------------------------
861   int i,j,k,m,thisE,otherE;
862   def R=basering;
863   intvec nulliv,chi_temp,kvec;
864   nulliv[size(iden)]=0;
865   list chi_E;
866   for(i=1;i<=size(iden);i++)
867   {
868      chi_E[i]=list();
869   }
870//---------------------------------------------------------------------------
871// Run through the list of charts and compute the Euler characteristic of
872// the new exceptional hypersurface and change the values for the old ones
873// according to the blow-up which has just been performed
874// For initialization reasons, treat the case of the first blow-up separately
875//---------------------------------------------------------------------------
876   for(i=2;i<=size(re[2]);i++)
877   {
878//--- run through all charts
879      if(defined(S)){kill S;}
880      def S=re[2][i];
881      setring S;
882      m=int(leadcoef(path[1,ncols(path)]));
883      if(defined(Spa)){kill Spa;}
884      def Spa=re[2][m];
885      if(size(BO[4])==1)
886      {
887//--- just one exceptional divisor
888         thisE=1;
889         setring Spa;
890         if(i==2)
891         {
892//--- have not set the initial value of chi(E_1) yet
893           if(dim(std(cent))==0)
894           {
895//--- center was point ==> new except. div. is a P^2
896              list templist=3*vdim(std(BO[1]+cent)),nulliv;
897           }
898           else
899           {
900//--- center was curve ==> new except. div. is curve x P^1
901              list templist=4-4*genus(BO[1]+cent),nulliv;
902           }
903           chi_E[1]=templist;
904           kill templist;
905         }
906         setring S;
907         i++;
908         if(i<size(re[2]))
909         {
910            continue;
911         }
912         else
913         {
914            break;
915         }
916      }
917      for(j=1;j<=size(iden);j++)
918      {
919//--- find out which exceptional divisor has just been born
920        if(inIVList(intvec(i,size(BO[4])),iden[j]))
921        {
922//--- found it
923           thisE=j;
924           break;
925        }
926      }
927//--- now setup new chi and change the previous ones appropriately
928      setring Spa;
929      if(size(chi_E[thisE])==0)
930      {
931//--- have not set the initial value of chi(E_thisE) yet
932        if(dim(std(cent))==0)
933        {
934//--- center was point  ==> new except. div. is a P^2
935           list templist=3*vdim(std(BO[1]+cent)),nulliv;
936        }
937        else
938        {
939//--- center was curve   ==> new except. div. is a C x P^1
940           list templist=4-4*genus(BO[1]+cent),nulliv;
941        }
942        chi_E[thisE]=templist;
943        kill templist;
944      }
945      for(j=1;j<=size(BO[4]);j++)
946      {
947//--- we are in the parent ring ==> thisE is not yet born
948//--- all the other E_i have already been initialized, but the chi
949//--- might change with the current blow-up at cent
950         if(BO[6][j]==1)
951         {
952//--- ignore empty sets
953            j++;
954            if(j<=size(BO[4]))
955            {
956              continue;
957            }
958            else
959            {
960              break;
961            }
962         }
963         for(k=1;k<=size(iden);k++)
964         {
965//--- find global index of BO[4][j]
966            if(inIVList(intvec(m,j),iden[k]))
967            {
968               otherE=k;
969               break;
970            }
971         }
972         if(chi_E[otherE][2][thisE]==1)
973         {
974//--- already considered this one
975            j++;
976            if(j<=size(BO[4]))
977            {
978              continue;
979            }
980            else
981            {
982              break;
983            }
984         }
985//---------------------------------------------------------------------------
986// update chi according to the formula
987// chi(E_k^transf)=chi(E_k) - chi(C \cap E_k) + chi(E_k \cap E_new)
988// for convenience of implementation, we first compute
989//        chi(E_k) - chi(C \cap E_k)
990// and afterwards add the last term chi(E_k \cap E_new)
991//---------------------------------------------------------------------------
992         ideal CinE=std(cent+BO[4][j]+BO[1]);  // this is C \cap E_k
993         if(dim(CinE)==1)
994         {
995//--- center meets E_k in a curve
996            chi_temp[otherE]=chi_E[otherE][1]-(2-2*genus(CinE));
997         }
998         if(dim(CinE)==0)
999         {
1000//--- center meets E_k in points
1001            chi_temp[otherE]=chi_E[otherE][1]-vdim(std(CinE));
1002         }
1003         kill CinE;
1004         setring S;
1005//--- now we are back in the i-th ring in the list
1006         ideal CinE=std(BO[4][j]+BO[4][size(BO[4])]+BO[1]);
1007                                              // this is E_k \cap E_new
1008         if(dim(CinE)==1)
1009         {
1010//--- if the two divisors meet, they meet in a curve
1011            chi_E[otherE][1]=chi_temp[otherE]+(2-2*genus(CinE));
1012            chi_E[otherE][2][thisE]=1;         // this blow-up of E_k is done
1013         }
1014         kill CinE;
1015         setring Spa;
1016      }
1017   }
1018   setring R;
1019   return(chi_E);
1020}
1021//////////////////////////////////////////////////////////////////////////////
1022static
1023proc computeChiE_local(list re, list iden)
1024"Internal procedure - no help and no example available
1025"
1026{
1027//--- compute the Euler characteristic of the intersection of the
1028//--- exceptional hypersurfaces with \pi^-1(0) which can be of
1029//--- dimension 1 or 2 - not considering the components of the strict
1030//--- transform
1031
1032//----------------------------------------------------------------------------
1033// Initialization
1034//----------------------------------------------------------------------------
1035   int i,j,k,aa,m,n,thisE,otherE;
1036   def R=basering;
1037   intvec nulliv,chi_temp,kvec,dimEi,endiv;
1038   nulliv[size(iden)]=0;
1039   dimEi[size(iden)]=0;
1040   endiv[size(re[2])]=0;
1041   list chi_E;
1042   for(i=1;i<=size(iden);i++)
1043   {
1044      chi_E[i]=list();
1045   }
1046//---------------------------------------------------------------------------
1047// Run through the list of charts and compute the Euler characteristic of
1048// the new exceptional hypersurface and change the values for the old ones
1049// according to the blow-up which has just been performed
1050// For initialization reasons, treat the case of the first blow-up separately
1051//---------------------------------------------------------------------------
1052   for(i=2;i<=size(re[2]);i++)
1053   {
1054//--- run through all charts
1055      if(defined(S)){kill S;}
1056      def S=re[2][i];
1057      setring S;
1058      if(defined(EList))
1059      {
1060         endiv[i]=1;
1061      }
1062      m=int(leadcoef(path[1,ncols(path)]));
1063      if(defined(Spa)){kill Spa;}
1064      def Spa=re[2][m];
1065      if(size(BO[4])==1)
1066      {
1067//--- just one exceptional divisor
1068         thisE=1;
1069         setring Spa;
1070         if(i==2)
1071         {
1072//--- have not set the initial value of chi(E_1) yet
1073//--- in the local case, we need to know whether the center contains 0
1074           if(size(reduce(cent,std(maxideal(1))))!=0)
1075           {
1076//--- first center does not meet 0
1077              list templist=0,nulliv;
1078              dimEi[1]=-1;
1079           }
1080           else
1081           {
1082              if(dim(std(cent))==0)
1083              {
1084//--- center was point ==> new except. div. is a P^2
1085                 list templist=3*vdim(std(BO[1]+cent)),nulliv;
1086                 dimEi[1]=2;
1087              }
1088              else
1089              {
1090//--- center was curve ==> intersection of new exceptional divisor
1091//---                      with \pi^-1(0) is a curve, namely P^1
1092                 setring S;
1093                 list templist=2,nulliv;
1094                 dimEi[1]=1;
1095              }
1096           }
1097           chi_E[1]=templist;
1098           kill templist;
1099         }
1100         setring S;
1101         i++;
1102         if(i<size(re[2]))
1103         {
1104            continue;
1105         }
1106         else
1107         {
1108            break;
1109         }
1110      }
1111      for(j=1;j<=size(iden);j++)
1112      {
1113//--- find out which exceptional divisor has just been born
1114        if(inIVList(intvec(i,size(BO[4])),iden[j]))
1115        {
1116//--- found it
1117           thisE=j;
1118           break;
1119        }
1120      }
1121//--- now setup new chi and change the previous ones appropriately
1122      setring Spa;
1123      if(size(chi_E[thisE])==0)
1124      {
1125//--- have not set the initial value of chi(E_thisE) yet
1126        if(deg(std(cent+BO[5])[1])==0)
1127        {
1128           if(dim(std(cent))==0)
1129           {
1130//--- \pi^-1(0) does not meet the Q-point cent
1131              list templist=0,nulliv;
1132              dimEi[thisE]=-1;
1133           }
1134//--- if cent is a curve, the intersection point might simply be outside
1135//--- of this chart!!!
1136        }
1137        else
1138        {
1139           if(dim(std(cent))==0)
1140           {
1141//--- center was point  ==> new except. div. is a P^2
1142              list templist=3*vdim(std(BO[1]+cent)),nulliv;
1143              dimEi[thisE]=2;
1144           }
1145           else
1146           {
1147//--- center was curve   ==> new except. div. is a C x P^1
1148              if(dim(std(cent+BO[5]))==1)
1149              {
1150//--- whole curve is in \pi^-1(0)
1151                 list templist=4-4*genus(BO[1]+cent),nulliv;
1152                 dimEi[thisE]=2;
1153              }
1154              else
1155              {
1156//--- curve meets \pi^-1(0) in points
1157//--- in S, the intersection will be a curve!!!
1158                 setring S;
1159                 list templist=2-2*genus(BO[1]+BO[4][size(BO[4])]+BO[5]),nulliv;
1160                 dimEi[thisE]=1;
1161                 setring Spa;
1162              }
1163           }
1164        }
1165        if(defined(templist))
1166        {
1167          chi_E[thisE]=templist;
1168          kill templist;
1169        }
1170      }
1171      for(j=1;j<=size(BO[4]);j++)
1172      {
1173//--- we are in the parent ring ==> thisE is not yet born
1174//--- all the other E_i have already been initialized, but the chi
1175//--- might change with the current blow-up at cent
1176         if(BO[6][j]==1)
1177         {
1178//--- ignore empty sets
1179            j++;
1180            if(j<=size(BO[4]))
1181            {
1182              continue;
1183            }
1184            else
1185            {
1186              break;
1187            }
1188         }
1189         for(k=1;k<=size(iden);k++)
1190         {
1191//--- find global index of BO[4][j]
1192            if(inIVList(intvec(m,j),iden[k]))
1193            {
1194               otherE=k;
1195               break;
1196            }
1197         }
1198         if(dimEi[otherE]<=1)
1199         {
1200//--- dimEi[otherE]==-1: center leading to this E does not meet \pi^-1(0)
1201//--- dimEi[otherE]== 0: center leading to this E does not meet \pi^-1(0)
1202//---                   in any previously visited charts
1203//---                   maybe in some other branch later, but has nothing
1204//---                   to do with this center
1205//--- dimEi[otherE]== 1: E \cap \pi^-1(0) is curve
1206//---                   ==> chi is birational invariant
1207            j++;
1208            if(j<=size(BO[4]))
1209            {
1210              continue;
1211            }
1212            break;
1213         }
1214         if(chi_E[otherE][2][thisE]==1)
1215         {
1216//--- already considered this one
1217            j++;
1218            if(j<=size(BO[4]))
1219            {
1220              continue;
1221            }
1222            else
1223            {
1224              break;
1225            }
1226         }
1227//---------------------------------------------------------------------------
1228// update chi according to the formula
1229// chi(E_k^transf)=chi(E_k) - chi(C \cap E_k) + chi(E_k \cap E_new)
1230// for convenience of implementation, we first compute
1231//        chi(E_k) - chi(C \cap E_k)
1232// and afterwards add the last term chi(E_k \cap E_new)
1233//---------------------------------------------------------------------------
1234         ideal CinE=std(cent+BO[4][j]+BO[1]);  // this is C \cap E_k
1235         if(dim(CinE)==1)
1236         {
1237//--- center meets E_k in a curve
1238            chi_temp[otherE]=chi_E[otherE][1]-(2-2*genus(CinE));
1239         }
1240         if(dim(CinE)==0)
1241         {
1242//--- center meets E_k in points
1243            chi_temp[otherE]=chi_E[otherE][1]-vdim(std(CinE));
1244         }
1245         kill CinE;
1246         setring S;
1247//--- now we are back in the i-th ring in the list
1248         ideal CinE=std(BO[4][j]+BO[4][size(BO[4])]+BO[1]);
1249                                              // this is E_k \cap E_new
1250         if(dim(CinE)==1)
1251         {
1252//--- if the two divisors meet, they meet in a curve
1253            chi_E[otherE][1]=chi_temp[otherE][1]+(2-2*genus(CinE));
1254            chi_E[otherE][2][thisE]=1;         // this blow-up of E_k is done
1255         }
1256         kill CinE;
1257         setring Spa;
1258      }
1259   }
1260//--- we still need to clean-up the 1-dimensional E_i \cap \pi^-1(0)
1261   for(i=1;i<=size(dimEi);i++)
1262   {
1263      if(dimEi[i]!=1)
1264      {
1265//--- not 1-dimensional ==> skip
1266         i++;
1267         if(i>size(dimEi)) break;
1268         continue;
1269      }
1270      if(defined(myCharts)) {kill myCharts;}
1271      intvec myCharts;
1272      chi_E[i]=0;
1273      for(j=1;j<=size(re[2]);j++)
1274      {
1275         if(endiv[j]==0)
1276         {
1277//--- not an endChart ==> skip
1278            j++;
1279            if(j>size(re[2])) break;
1280            continue;
1281         }
1282         if(defined(mtuple)) {kill mtuple;}
1283         intvec mtuple=findInIVList(1,j,iden[i]);
1284         if(size(mtuple)==1)
1285         {
1286//-- nothing to do with this Ei ==> skip
1287            j++;
1288            if(j>size(re[2])) break;
1289            continue;
1290         }
1291         myCharts[size(myCharts)+1]=j;
1292         if(defined(S)){kill S;}
1293         def S=re[2][j];
1294         setring S;
1295         if(defined(interId)){kill interId;}
1296//--- all components
1297         ideal interId=std(BO[4][mtuple[2]]+BO[5]);
1298         if(defined(myPts)){kill myPts;}
1299         ideal myPts=1;
1300         export(myPts);
1301         export(interId);
1302         if(defined(doneId)){kill doneId;}
1303         if(defined(donePts)){kill donePts;}
1304         ideal donePts=1;
1305         ideal doneId=1;
1306         for(k=2;k<size(myCharts);k++)
1307         {
1308//--- fetch the components which have already been dealt with via fetchInTree
1309            if(defined(opath)) {kill opath;}
1310            def opath=imap(re[2][myCharts[k][1]],path);
1311            aa=1;
1312            while((aa<ncols(opath))&&(aa<ncols(path)))
1313            {
1314               if(path[1,aa+1]!=opath[1,aa+1]) break;
1315               aa++;
1316            }
1317            if(defined(comPa)) {kill comPa;}
1318            int comPa=int(leadcoef(path[1,aa]));
1319            if(defined(tempId)){kill tempId;}
1320            ideal tempId=fetchInTree(re,myCharts[k][1],comPa,j,"interId",iden);
1321            doneId=intersect(doneId,tempId);
1322            kill tempId;
1323            ideal tempId=fetchInTree(re,myCharts[k][1],comPa,j,"myPts",iden);
1324            donePts=intersect(donePts,tempId);
1325            kill tempId;
1326         }
1327//--- drop components which have already been dealt with
1328         interId=sat(interId,doneId)[1];
1329         list pr=minAssGTZ(interId);
1330         myPts=std(interId+doneId);
1331         for(k=1;k<=size(pr);k++)
1332         {
1333           for(n=k+1;n<=size(pr);n++)
1334           {
1335              myPts=intersect(myPts,std(pr[k]+pr[n]));
1336           }
1337           if(deg(std(pr[k])[1])>0)
1338           {
1339              chi_E[i][1]=chi_E[i][1]+(2-2*genus(pr[k]));
1340           }
1341         }
1342         myPts=sat(myPts,donePts)[1];
1343         chi_E[i][1]=chi_E[i][1]-vdim(myPts);
1344      }
1345   }
1346   setring R;
1347   return(chi_E);
1348}
1349//////////////////////////////////////////////////////////////////////////////
1350static
1351proc chi_ast(list re,list iden,list #)
1352"Internal procedure - no help and no example available
1353"
1354{
1355//--- compute the Euler characteristic of the Ei,Eij,Eijk and the
1356//--- corresponding Ei^*,Eij^*,Eijk^* by preparing the input to the
1357//--- specialized auxilliary procedures and then recombining the results
1358
1359//----------------------------------------------------------------------------
1360// Initialization
1361//----------------------------------------------------------------------------
1362   int i,j,k,g;
1363   intvec tiv;
1364   list chi_ijk,chi_ij,chi_i,ast_ijk,ast_ij,ast_i,tmplist,g_ij,emptylist;
1365   list leererSchnitt;
1366   def R=basering;
1367   ring Rhelp=0,@t,dp;
1368   setring R;
1369//----------------------------------------------------------------------------
1370// first compute the chi(Eij) and  at the same time
1371// check whether E_i \cap E_j is empty
1372// the formula is
1373//              chi_ij=2-2*genus(E_i \cap E_j)
1374//----------------------------------------------------------------------------
1375   if(size(#)>0)
1376   {
1377      "Entering chi_ast";
1378   }
1379   for(i=1;i<=size(iden)-1;i++)
1380   {
1381      for(j=i+1;j<=size(iden);j++)
1382      {
1383         if(defined(blub)){kill blub;}
1384         def blub=chiEij(re,iden,intvec(i,j));
1385         if(typeof(blub)=="int")
1386         {
1387            tmplist=intvec(i,j),blub;
1388         }
1389         else
1390         {
1391            leererSchnitt[size(leererSchnitt)+1]=intvec(i,j);
1392            tmplist=intvec(i,j),0;
1393         }
1394         chi_ij[size(chi_ij)+1]=tmplist;
1395      }
1396   }
1397   if(size(#)>0)
1398   {
1399      "chi_ij computed";
1400   }
1401//-----------------------------------------------------------------------------
1402// compute chi(Eijk)=chi^*(Eijk) by counting the points in the intersection
1403//      chi_ijk=#(E_i \cap E_j \cap E_k)
1404//      ast_ijk=chi_ijk
1405//-----------------------------------------------------------------------------
1406   for(i=1;i<=size(iden)-2;i++)
1407   {
1408      for(j=i+1;j<=size(iden)-1;j++)
1409      {
1410         for(k=j+1;k<=size(iden);k++)
1411         {
1412            if(inIVList(intvec(i,j),leererSchnitt))
1413            {
1414               tmplist=intvec(i,j,k),0;
1415            }
1416            else
1417            {
1418               tmplist=intvec(i,j,k),countEijk(re,iden,intvec(i,j,k));
1419            }
1420            chi_ijk[size(chi_ijk)+1]=tmplist;
1421         }
1422      }
1423   }
1424   ast_ijk=chi_ijk;
1425   if(size(#)>0)
1426   {
1427      "chi_ijk computed";
1428   }
1429//----------------------------------------------------------------------------
1430// construct chi(Eij^*) by the formula
1431//      ast_ij=chi_ij - sum_ijk chi_ijk,
1432// where k runs over all indices != i,j
1433//----------------------------------------------------------------------------
1434   for(i=1;i<=size(chi_ij);i++)
1435   {
1436      ast_ij[i]=chi_ij[i];
1437      for(k=1;k<=size(chi_ijk);k++)
1438      {
1439         if(((chi_ijk[k][1][1]==chi_ij[i][1][1])||
1440                 (chi_ijk[k][1][2]==chi_ij[i][1][1]))&&
1441            ((chi_ijk[k][1][2]==chi_ij[i][1][2])||
1442                 (chi_ijk[k][1][3]==chi_ij[i][1][2])))
1443         {
1444            ast_ij[i][2]=ast_ij[i][2]-chi_ijk[k][2];
1445         }
1446      }
1447   }
1448   if(size(#)>0)
1449   {
1450      "ast_ij computed";
1451   }
1452//----------------------------------------------------------------------------
1453// construct ast_i according to the following formulae
1454//      ast_i=0 if E_i is (Q- resp. C-)component of the strict transform
1455//      chi_i=3*n if E_i originates from blowing up a Q-point,
1456//                which consists of n (different) C-points
1457//      chi_i=2-2g(C) if E_i originates from blowing up a (Q-)curve C
1458//           (chi_i=n*(2-2g(C_i))=2-2g(C),
1459//                 where C=\cup C_i, C_i \cap C_j = \emptyset)
1460// if E_i is not a component of the strict transform, then
1461//       ast_i=chi_i - sum_{j!=i} ast_ij
1462//----------------------------------------------------------------------------
1463   for(i=1;i<=size(iden);i++)
1464   {
1465      if(defined(S)) {kill S;}
1466      def S=re[2][iden[i][1][1]];
1467      setring S;
1468      if(iden[i][1][2]>size(BO[4]))
1469      {
1470         i--;
1471         break;
1472      }
1473   }
1474   list idenE=iden;
1475   while(size(idenE)>i)
1476   {
1477      idenE=delete(idenE,size(idenE));
1478   }
1479   list cl=computeChiE(re,idenE);
1480   for(i=1;i<=size(idenE);i++)
1481   {
1482      chi_i[i]=list(intvec(i),cl[i][1]);
1483   }
1484   if(size(#)>0)
1485   {
1486      "chi_i computed";
1487   }
1488   for(i=1;i<=size(idenE);i++)
1489   {
1490      ast_i[i]=chi_i[i];
1491      for(j=1;j<=size(ast_ij);j++)
1492      {
1493         if((ast_ij[j][1][1]==i)||(ast_ij[j][1][2]==i))
1494         {
1495            ast_i[i][2]=ast_i[i][2]-chi_ij[j][2];
1496         }
1497      }
1498      for(j=1;j<=size(ast_ijk);j++)
1499      {
1500         if((ast_ijk[j][1][1]==i)||(ast_ijk[j][1][2]==i)
1501                                 ||(ast_ijk[j][1][3]==i))
1502         {
1503            ast_i[i][2]=ast_i[i][2]+chi_ijk[j][2];
1504         }
1505      }
1506   }
1507   for(i=size(idenE)+1;i<=size(iden);i++)
1508   {
1509      ast_i[i]=list(intvec(i),0);
1510   }
1511//--- results are in ast_i, ast_ij and ast_ijk
1512//--- all are of the form intvec(indices),int(value)
1513   list result=ast_i,ast_ij,ast_ijk;
1514   return(result);
1515}
1516//////////////////////////////////////////////////////////////////////////////
1517static
1518proc chi_ast_local(list re,list iden,list #)
1519"Internal procedure - no help and no example available
1520"
1521{
1522//--- compute the Euler characteristic of the Ei,Eij,Eijk and the
1523//--- corresponding Ei^*,Eij^*,Eijk^* by preparing the input to the
1524//--- specialized auxilliary procedures and then recombining the results
1525
1526//----------------------------------------------------------------------------
1527// Initialization
1528//----------------------------------------------------------------------------
1529   int i,j,k,g;
1530   intvec tiv;
1531   list chi_ijk,chi_ij,chi_i,ast_ijk,ast_ij,ast_i,tmplist,g_ij,emptylist;
1532   list leererSchnitt;
1533   def R=basering;
1534   ring Rhelp=0,@t,dp;
1535   setring R;
1536//----------------------------------------------------------------------------
1537// first compute
1538// if E_i \cap E_j \cap \pi^-1(0) is a curve:
1539//    chi(Eij) and  at the same time
1540//    check whether E_i \cap E_j is empty
1541//    the formula is
1542//              chi_ij=2-2*genus(E_i \cap E_j)
1543// otherwise (points):
1544//    chi(E_ij) by counting the points
1545//----------------------------------------------------------------------------
1546   if(size(#)>0)
1547   {
1548      "Entering chi_ast_local";
1549   }
1550   for(i=1;i<=size(iden)-1;i++)
1551   {
1552      for(j=i+1;j<=size(iden);j++)
1553      {
1554         if(defined(blub)){kill blub;}
1555         def blub=chiEij_local(re,iden,intvec(i,j));
1556         if(typeof(blub)=="int")
1557         {
1558            tmplist=intvec(i,j),blub;
1559         }
1560         else
1561         {
1562            leererSchnitt[size(leererSchnitt)+1]=intvec(i,j);
1563            tmplist=intvec(i,j),0;
1564         }
1565         chi_ij[size(chi_ij)+1]=tmplist;
1566      }
1567   }
1568   if(size(#)>0)
1569   {
1570      "chi_ij computed";
1571   }
1572//-----------------------------------------------------------------------------
1573// compute chi(Eijk)=chi^*(Eijk) by counting the points in the intersection
1574//      chi_ijk=#(E_i \cap E_j \cap E_k \cap \pi^-1(0))
1575//      ast_ijk=chi_ijk
1576//-----------------------------------------------------------------------------
1577   for(i=1;i<=size(iden)-2;i++)
1578   {
1579      for(j=i+1;j<=size(iden)-1;j++)
1580      {
1581         for(k=j+1;k<=size(iden);k++)
1582         {
1583            if(inIVList(intvec(i,j),leererSchnitt))
1584            {
1585               tmplist=intvec(i,j,k),0;
1586            }
1587            else
1588            {
1589               tmplist=intvec(i,j,k),countEijk(re,iden,intvec(i,j,k),"local");
1590            }
1591            chi_ijk[size(chi_ijk)+1]=tmplist;
1592         }
1593      }
1594   }
1595   ast_ijk=chi_ijk;
1596   if(size(#)>0)
1597   {
1598      "chi_ijk computed";
1599   }
1600//----------------------------------------------------------------------------
1601// construct chi(Eij^*) by the formula
1602//      ast_ij=chi_ij - sum_ijk chi_ijk,
1603// where k runs over all indices != i,j
1604//----------------------------------------------------------------------------
1605   for(i=1;i<=size(chi_ij);i++)
1606   {
1607      ast_ij[i]=chi_ij[i];
1608      for(k=1;k<=size(chi_ijk);k++)
1609      {
1610         if(((chi_ijk[k][1][1]==chi_ij[i][1][1])||
1611                 (chi_ijk[k][1][2]==chi_ij[i][1][1]))&&
1612            ((chi_ijk[k][1][2]==chi_ij[i][1][2])||
1613                 (chi_ijk[k][1][3]==chi_ij[i][1][2])))
1614         {
1615            ast_ij[i][2]=ast_ij[i][2]-chi_ijk[k][2];
1616         }
1617      }
1618   }
1619   if(size(#)>0)
1620   {
1621      "ast_ij computed";
1622   }
1623//----------------------------------------------------------------------------
1624// construct ast_i according to the following formulae
1625//      ast_i=0 if E_i is (Q- resp. C-)component of the strict transform
1626// if E_i \cap \pi^-1(0) is of dimension 2:
1627//      chi_i=3*n if E_i originates from blowing up a Q-point,
1628//                which consists of n (different) C-points
1629//      chi_i=2-2g(C) if E_i originates from blowing up a (Q-)curve C
1630//           (chi_i=n*(2-2g(C_i))=2-2g(C),
1631//                 where C=\cup C_i, C_i \cap C_j = \emptyset)
1632// if E_i \cap \pi^-1(0) is a curve:
1633//      use the formula chi_i=2-2*genus(E_i \cap \pi^-1(0))
1634//
1635// for E_i not a component of the strict transform we have
1636//       ast_i=chi_i - sum_{j!=i} ast_ij
1637//----------------------------------------------------------------------------
1638   for(i=1;i<=size(iden);i++)
1639   {
1640      if(defined(S)) {kill S;}
1641      def S=re[2][iden[i][1][1]];
1642      setring S;
1643      if(iden[i][1][2]>size(BO[4]))
1644      {
1645         i--;
1646         break;
1647      }
1648   }
1649   list idenE=iden;
1650   while(size(idenE)>i)
1651   {
1652      idenE=delete(idenE,size(idenE));
1653   }
1654   list cl=computeChiE_local(re,idenE);
1655   for(i=1;i<=size(cl);i++)
1656   {
1657      if(size(cl[i])==0)
1658      {
1659         cl[i][1]=0;
1660      }
1661   }
1662   for(i=1;i<=size(idenE);i++)
1663   {
1664      chi_i[i]=list(intvec(i),cl[i][1]);
1665   }
1666   if(size(#)>0)
1667   {
1668      "chi_i computed";
1669   }
1670   for(i=1;i<=size(idenE);i++)
1671   {
1672      ast_i[i]=chi_i[i];
1673      for(j=1;j<=size(ast_ij);j++)
1674      {
1675         if((ast_ij[j][1][1]==i)||(ast_ij[j][1][2]==i))
1676         {
1677            ast_i[i][2]=ast_i[i][2]-chi_ij[j][2];
1678         }
1679      }
1680      for(j=1;j<=size(ast_ijk);j++)
1681      {
1682         if((ast_ijk[j][1][1]==i)||(ast_ijk[j][1][2]==i)
1683                                 ||(ast_ijk[j][1][3]==i))
1684         {
1685            ast_i[i][2]=ast_i[i][2]+chi_ijk[j][2];
1686         }
1687      }
1688   }
1689   for(i=size(idenE)+1;i<=size(iden);i++)
1690   {
1691      ast_i[i]=list(intvec(i),0);
1692   }
1693//--- results are in ast_i, ast_ij and ast_ijk
1694//--- all are of the form intvec(indices),int(value)
1695//"End of chi_ast_local";
1696//~;
1697   list result=ast_i,ast_ij,ast_ijk;
1698   return(result);
1699}
1700//////////////////////////////////////////////////////////////////////////////
1701
1702proc discrepancy(list re)
1703"USAGE:   discrepancy(L);
1704@*        L    = list of rings
1705ASSUME:   L is the output of resolution of singularities
1706RETRUN:   discrepancies of the given resolution"
1707{
1708//----------------------------------------------------------------------------
1709// Initialization
1710//----------------------------------------------------------------------------
1711   def R=basering;
1712   int i,j;
1713   list iden=prepEmbDiv(re);       //--- identify the E_i
1714   intvec Vvec=computeV(re,iden);  //--- nu
1715   intvec Nvec=computeN(re,iden);  //--- N
1716   intvec Avec;
1717//--- only look at exceptional divisors, not at strict transform
1718   for(i=1;i<=size(iden);i++)
1719   {
1720      if(defined(S)) {kill S;}
1721      def S=re[2][iden[i][1][1]];
1722      setring S;
1723      if(iden[i][1][2]>size(BO[4]))
1724      {
1725         i--;
1726         break;
1727      }
1728   }
1729   j=i;
1730//--- discrepancies are a_i=nu_i-N_i
1731   for(i=1;i<=j;i++)
1732   {
1733     Avec[i]=Vvec[i]-Nvec[i]-1;
1734   }
1735   return(Avec);
1736}
1737example
1738{"EXAMPLE:";
1739   echo = 2;
1740   ring R=0,(x,y,z),dp;
1741   ideal I=x2+y2+z3;
1742   list re=resolve(I);
1743   discrepancy(re);
1744}
1745//////////////////////////////////////////////////////////////////////////////
1746
1747proc zetaDL(list re,int d,list #)
1748"USAGE:   zetaDL(L,d[,s1][,s2][,a]);
1749          L     = list of rings;
1750          d     = integer;
1751          s1,s2 = string;
1752          a     = integer
1753ASSUME:   L is the output of resolution of singularities
1754COMPUTE:  local Denef-Loeser zeta function, if string s1 is present and
1755             has the value 'local'; global Denef-Loeser zeta function
1756             otherwise
1757          if string s1 or s2 has the value "A", additionally the
1758             characteristic polynomial of the monodromy is computed
1759RETURN:   list l
1760          if a is not present:
1761          l[1]: string specifying the top. zeta function
1762          l[2]: string specifying characteristic polynomial of monodromy,
1763                if "A" was specified
1764          if a is present:
1765          l[1]: string specifying the top. zeta function
1766          l[2]: list ast,
1767                     ast[1]=chi(Ei^*)
1768                     ast[2]=chi(Eij^*)
1769                     ast[3]=chi(Eijk^*)
1770          l[3]: intvec nu of multiplicites as needed in computation of zeta
1771                function
1772          l[4]: intvec N of multiplicities as needed in compuation of zeta
1773                function
1774          l[5]: string specifying characteristic polynomial of monodromy,
1775                if "A" was specified
1776EXAMPLE:  example zetaDL;   shows an example
1777"
1778{
1779//----------------------------------------------------------------------------
1780// Initialization
1781//----------------------------------------------------------------------------
1782   def R=basering;
1783   int show_all,i;
1784   if(size(#)>0)
1785   {
1786     if((typeof(#[1])=="int")||(size(#)>2))
1787     {
1788       show_all=1;
1789     }
1790     if(typeof(#[1])=="string")
1791     {
1792       if((#[1]=="local")||(#[1]=="lokal"))
1793       {
1794//          ERROR("Local case not implemented yet");
1795          "Local Case: Assuming that no (!) charts were dropped";
1796          "during calculation of the resolution (option \"A\")";
1797          int localComp=1;
1798          if(size(#)>1)
1799          {
1800             if(#[2]=="A")
1801             {
1802                int aCampoFormula=1;
1803             }
1804          }
1805       }
1806       else
1807       {
1808          if(#[1]=="A")
1809          {
1810             int aCampoFormula=1;
1811          }
1812          "Computing global zeta function";
1813       }
1814     }
1815   }
1816//----------------------------------------------------------------------------
1817// Identify the embedded divisors and chi(Ei^*), chi(Eij^*) and chi(Eijk^*)
1818// as well as the integer vector V(=nu) and N
1819//----------------------------------------------------------------------------
1820   list iden=prepEmbDiv(re);       //--- identify the E_i
1821//!!! TIMING:    E8 takes 520 sec ==> needs speed up
1822   if(!defined(localComp))
1823   {
1824      list ast_list=chi_ast(re,iden); //--- compute chi(E^*)
1825   }
1826   else
1827   {
1828      list ast_list=chi_ast_local(re,iden);
1829   }
1830   intvec Vvec=computeV(re,iden);  //--- nu
1831   intvec Nvec=computeN(re,iden);  //--- N
1832//----------------------------------------------------------------------------
1833// Build a new ring with one parameter s
1834// and compute Zeta_top^(d) in its ground field
1835//----------------------------------------------------------------------------
1836   ring Qs=(0,s),x,dp;
1837   number zetaTop=0;
1838   number enum,denom;
1839   denom=1;
1840   for(i=1;i<=size(Nvec);i++)
1841   {
1842      denom=denom*(Vvec[i]+s*Nvec[i]);
1843   }
1844//--- factors for which index set J consists of one element
1845//--- (do something only if d divides N_j)
1846   for(i=1;i<=size(ast_list[1]);i++)
1847   {
1848      if((((Nvec[ast_list[1][i][1][1]]/d)*d)-Nvec[ast_list[1][i][1][1]]==0)&&
1849         (ast_list[1][i][2]!=0))
1850      {
1851          enum=enum+ast_list[1][i][2]*(denom/(Vvec[ast_list[1][i][1][1]]+s*Nvec[ast_list[1][i][1][1]]));
1852      }
1853   }
1854//--- factors for which index set J consists of two elements
1855//--- (do something only if d divides both N_i and N_j)
1856//!!! TIMING: E8 takes 690 sec and has 703 elements
1857//!!!         ==> need to implement a smarter way to do this
1858//!!! e.g. build up enumerator and denominator separately, thus not
1859//!!!      searching for common factors in each step
1860   for(i=1;i<=size(ast_list[2]);i++)
1861   {
1862      if((((Nvec[ast_list[2][i][1][1]]/d)*d)-Nvec[ast_list[2][i][1][1]]==0)&&
1863         (((Nvec[ast_list[2][i][1][2]]/d)*d)-Nvec[ast_list[2][i][1][2]]==0)&&
1864          (ast_list[2][i][2]!=0))
1865      {
1866         enum=enum+ast_list[2][i][2]*(denom/((Vvec[ast_list[2][i][1][1]]+s*Nvec[ast_list[2][i][1][1]])*(Vvec[ast_list[2][i][1][2]]+s*Nvec[ast_list[2][i][1][2]])));
1867      }
1868   }
1869//--- factors for which index set J consists of three elements
1870//--- (do something only if d divides N_i, N_j and N_k)
1871//!!! TIMING: E8 takes 490 sec and has 8436 elements
1872//!!!         ==> same kind of improvements as in the previous case needed
1873   for(i=1;i<=size(ast_list[3]);i++)
1874   {
1875      if((((Nvec[ast_list[3][i][1][1]]/d)*d)-Nvec[ast_list[3][i][1][1]]==0)&&
1876         (((Nvec[ast_list[3][i][1][2]]/d)*d)-Nvec[ast_list[3][i][1][2]]==0)&&
1877         (((Nvec[ast_list[3][i][1][3]]/d)*d)-Nvec[ast_list[3][i][1][3]]==0)&&
1878         (ast_list[3][i][2]!=0))
1879      {
1880         enum=enum+ast_list[3][i][2]*(denom/((Vvec[ast_list[3][i][1][1]]+s*Nvec[ast_list[3][i][1][1]])*(Vvec[ast_list[3][i][1][2]]+s*Nvec[ast_list[3][i][1][2]])*(Vvec[ast_list[3][i][1][3]]+s*Nvec[ast_list[3][i][1][3]])));
1881      }
1882   }
1883   zetaTop=enum/denom;
1884   zetaTop=numerator(zetaTop)/denominator(zetaTop);
1885   string zetaStr=string(zetaTop);
1886
1887   if(show_all)
1888   {
1889      list result=zetaStr,ast_list[1],ast_list[2],ast_list[3],Vvec,Nvec;
1890   }
1891   else
1892   {
1893      list result=zetaStr;
1894   }
1895//--- compute characteristic polynomial of the monodromy
1896//--- by the A'Campo formula
1897   if(defined(aCampoFormula))
1898   {
1899      poly charP=1;
1900      for(i=1;i<=size(ast_list[1]);i++)
1901      {
1902         charP=charP*((s^Nvec[i]-1)^ast_list[1][i][2]);
1903      }
1904      string charPStr=string(charP/(s-1));
1905      result[size(result)+1]=charPStr;
1906   }
1907   setring R;
1908   return(result);
1909}
1910example
1911{"EXAMPLE:";
1912   echo = 2;
1913   ring R=0,(x,y,z),dp;
1914   ideal I=x2+y2+z3;
1915   list re=resolve(I,"K");
1916   zetaDL(re,1);
1917   I=(xz+y2)*(xz+y2+x2)+z5;
1918   list L=resolve(I,"K");
1919   zetaDL(L,1);
1920
1921//===== expected zeta function =========
1922// (20s^2+130s+87)/((1+s)*(3+4s)*(29+40s))
1923//======================================
1924}
1925//////////////////////////////////////////////////////////////////////////////
1926
1927proc abstractR(list re)
1928"USAGE:   abstractR(L);
1929@*        L = list of rings
1930ASSUME:   L is output of resolution of singularities
1931NOTE:     currently only implemented for isolated surface singularities
1932RETURN:   list l
1933          l[1]: intvec, where
1934                   l[1][i]=1 if the corresponding ring is a final chart
1935                             of non-embedded resolution
1936                   l[1][i]=0 otherwise
1937          l[2]: intvec, where
1938                   l[2][i]=1 if the corresponding ring does not occur
1939                             in the non-embedded resolution
1940                   l[2][i]=0 otherwise
1941          l[3]: list L
1942EXAMPLE:  example abstractR;   shows an example
1943"
1944{
1945//---------------------------------------------------------------------------
1946// Initialization and sanity checks
1947//---------------------------------------------------------------------------
1948   def R=basering;
1949//---Test whether we are in the irreducible surface case
1950   def S=re[2][1];
1951   setring S;
1952   BO[2]=BO[2]+BO[1];
1953   if(dim(std(BO[2]))!=2)
1954   {
1955       ERROR("NOT A SURFACE");
1956   }
1957   if(dim(std(slocus(BO[2])))>0)
1958   {
1959       ERROR("NOT AN ISOLATED SINGULARITY");
1960   }
1961   setring R;
1962   int i,j,k,l,i0;
1963   intvec deleted;
1964   intvec endiv;
1965   endiv[size(re[2])]=0;
1966   deleted[size(re[2])]=0;
1967//-----------------------------------------------------------------------------
1968// run through all rings, only consider final charts
1969// for each final chart follow the list of charts leading up to it until
1970//     we encounter a chart which is not finished in the non-embedded case
1971//-----------------------------------------------------------------------------
1972   for(i=1;i<=size(re[2]);i++)
1973   {
1974      if(defined(S)){kill S;}
1975      def S=re[2][i];
1976      setring S;
1977      if(size(reduce(cent,std(BO[2]+BO[1])))!=0)
1978      {
1979//--- only consider endrings
1980         i++;
1981         continue;
1982      }
1983      i0=i;
1984      for(j=ncols(path);j>=2;j--)
1985      {
1986//--- walk backwards through history
1987        if(j==2)
1988        {
1989          endiv[i0]=1;
1990          break;
1991        }
1992        k=int(leadcoef(path[1,j]));
1993        if((deleted[k]==1)||(endiv[k]==1))
1994        {
1995          deleted[i0]=1;
1996          break;
1997        }
1998        if(defined(SPa)){kill SPa;}
1999        def SPa=re[2][k];
2000        setring SPa;
2001        l=int(leadcoef(path[1,ncols(path)]));
2002        if(defined(SPa2)){kill SPa2;}
2003        def SPa2=re[2][l];
2004        setring SPa2;
2005        if((deleted[l]==1)||(endiv[l]==1))
2006        {
2007//--- parent was already treated via different final chart
2008//--- we may safely inherit the data
2009          deleted[i0]=1;
2010          setring S;
2011          i0=k;
2012          j--;
2013          continue;
2014        }
2015        setring SPa;
2016//!!! Idea of Improvement:
2017//!!! BESSER: rueckwaerts gehend nur testen ob glatt
2018//!!!         danach vorwaerts bis zum ersten Mal abstractNC
2019//!!! ACHTUNG: rueckweg unterwegs notieren - wir haben nur vergangenheit!
2020        if((deg(std(slocus(BO[2]))[1])!=0)||(!abstractNC(BO)))
2021        {
2022//--- not finished in the non-embedded case
2023           endiv[i0]=1;
2024           break;
2025        }
2026//--- unnecessary chart in non-embedded case
2027        setring S;
2028        deleted[i0]=1;
2029        i0=k;
2030      }
2031   }
2032//-----------------------------------------------------------------------------
2033// Clean up the intvec deleted and return the result
2034//-----------------------------------------------------------------------------
2035   setring R;
2036   for(i=1;i<=size(endiv);i++)
2037   {
2038     if(endiv[i]==1)
2039     {
2040        if(defined(S)) {kill S;}
2041        def S=re[2][i];
2042        setring S;
2043        for(j=3;j<ncols(path);j++)
2044        {
2045           if((endiv[int(leadcoef(path[1,j]))]==1)||
2046              (deleted[int(leadcoef(path[1,j]))]==1))
2047           {
2048              deleted[int(leadcoef(path[1,j+1]))]=1;
2049              endiv[int(leadcoef(path[1,j+1]))]=0;
2050           }
2051        }
2052        if((endiv[int(leadcoef(path[1,ncols(path)]))]==1)||
2053           (deleted[int(leadcoef(path[1,ncols(path)]))]==1))
2054        {
2055           deleted[i]=1;
2056           endiv[i]=0;
2057        }
2058     }
2059   }
2060   list resu=endiv,deleted,re;
2061   return(resu);
2062}
2063example
2064{"EXAMPLE:";
2065   echo = 2;
2066   ring r = 0,(x,y,z),dp;
2067   ideal I=x2+y2+z11;
2068   list L=resolve(I);
2069   list absR=abstractR(L);
2070   absR[1];
2071   absR[2];
2072}
2073//////////////////////////////////////////////////////////////////////////////
2074static
2075proc decompE(list BO)
2076"Internal procedure - no help and no example available
2077"
2078{
2079//--- compute the list of exceptional divisors, including the components
2080//--- of the strict transform in the non-embedded case
2081//--- (computation over Q !!!)
2082   def R=basering;
2083   list Elist,prList;
2084   int i;
2085   for(i=1;i<=size(BO[4]);i++)
2086   {
2087      Elist[i]=BO[4][i];
2088   }
2089/* practical speed up (part 1 of 3) -- no theoretical relevance
2090   ideal M=maxideal(1);
2091   M[1]=var(nvars(basering));
2092   M[nvars(basering)]=var(1);
2093   map phi=R,M;
2094*/
2095   ideal KK=BO[2];
2096
2097/* practical speed up (part 2 of 3)
2098   KK=phi(KK);
2099*/
2100   prList=minAssGTZ(KK);
2101
2102/* practical speed up (part 3 of 3)
2103   prList=phi(prList);
2104*/
2105
2106   for(i=1;i<=size(prList);i++)
2107   {
2108      Elist[size(BO[4])+i]=prList[i];
2109   }
2110   return(Elist);
2111}
2112//////////////////////////////////////////////////////////////////////////////
2113
2114proc prepEmbDiv(list re, list #)
2115"USAGE:   prepEmbDiv(L[,a]);
2116@*        L = list of rings
2117@*        a = integer
2118ASSUME:   L is output of resolution of singularities
2119COMPUTE:  if a is not present: exceptional divisors including components
2120          of the strict transform
2121          otherwise: only exceptional divisors
2122RETURN:   list of Q-irreducible exceptional divisors (embedded case)
2123EXAMPLE:  example prepEmbDiv;   shows an example
2124"
2125{
2126//--- 1) in each final chart, a list of (decomposed) exceptional divisors
2127//---    is created (and exported)
2128//--- 2) the strict transform is decomposed
2129//--- 3) the exceptional divisors (including the strict transform)
2130//---    in the different charts are compared, identified and this
2131//---    information collected into a list which is then returned
2132//---------------------------------------------------------------------------
2133// Initialization
2134//---------------------------------------------------------------------------
2135   int i,j,k,ncomps,offset,found,a,b,c,d;
2136   list tmpList;
2137   def R=basering;
2138//--- identify identical exceptional divisors
2139//--- (note: we are in the embedded case)
2140   list iden=collectDiv(re)[2];
2141//---------------------------------------------------------------------------
2142// Go to each final chart and create the EList
2143//---------------------------------------------------------------------------
2144   for(i=1;i<=size(iden[size(iden)]);i++)
2145   {
2146      if(defined(S)){kill S;}
2147      def S=re[2][iden[size(iden)][i][1]];
2148      setring S;
2149      if(defined(EList)){kill EList;}
2150      list EList=decompE(BO);
2151      export(EList);
2152      setring R;
2153      kill S;
2154   }
2155//--- save original iden for further use and then drop
2156//--- strict transform from it
2157   list iden0=iden;
2158   iden=delete(iden,size(iden));
2159   if(size(#)>0)
2160   {
2161//--- we are not interested in the strict transform of X
2162      return(iden);
2163   }
2164//----------------------------------------------------------------------------
2165// Run through all final charts and collect and identify all components of
2166// the strict transform
2167//----------------------------------------------------------------------------
2168//--- first final chart - to be used for initialization
2169   def S=re[2][iden0[size(iden0)][1][1]];
2170   setring S;
2171   ncomps=size(EList)-size(BO[4]);
2172   if((ncomps==1)&&(deg(std(EList[size(EList)])[1])==0))
2173   {
2174      ncomps=0;
2175   }
2176   offset=size(BO[4]);
2177   for(i=1;i<=ncomps;i++)
2178   {
2179//--- add components of strict transform
2180      tmpList[1]=intvec(iden0[size(iden0)][1][1],size(BO[4])+i);
2181      iden[size(iden)+1]=tmpList;
2182   }
2183//--- now run through the other final charts
2184   for(i=2;i<=size(iden0[size(iden0)]);i++)
2185   {
2186      if(defined(S2)){kill S2;}
2187      def S2=re[2][iden0[size(iden0)][i][1]];
2188      setring S2;
2189//--- determine common parent of this ring and re[2][iden0[size(iden0)][1][1]]
2190      if(defined(opath)){kill opath;}
2191      def opath=imap(S,path);
2192      j=1;
2193      while(opath[1,j]==path[1,j])
2194      {
2195         j++;
2196         if((j>ncols(path))||(j>ncols(opath))) break;
2197      }
2198      if(defined(li1)){kill li1;}
2199      list li1;
2200//--- fetch the components we have considered in
2201//--- re[2][iden0[size(iden0)][1][1]]
2202//--- via the resolution tree
2203      for(k=1;k<=ncomps;k++)
2204      {
2205         if(defined(id1)){kill id1;}
2206         string tempstr="EList["+string(eval(k+offset))+"]";
2207         ideal id1=fetchInTree(re,iden0[size(iden0)][1][1],
2208                               int(leadcoef(path[1,j-1])),
2209                               iden0[size(iden0)][i][1],tempstr,iden0,1);
2210         kill tempstr;
2211         li1[k]=id1;
2212         kill id1;
2213      }
2214//--- do the comparison
2215      for(k=size(BO[4])+1;k<=size(EList);k++)
2216      {
2217//--- only components of the strict transform are interesting
2218         if((size(BO[4])+1==size(EList))&&(deg(std(EList[size(EList)])[1])==0))
2219         {
2220            break;
2221         }
2222         found=0;
2223         for(j=1;j<=size(li1);j++)
2224         {
2225            if((size(reduce(li1[j],std(EList[k])))==0)&&
2226               (size(reduce(EList[k],std(li1[j])))==0))
2227            {
2228//--- found a match
2229               li1[j]=ideal(1);
2230               iden[size(iden0)-1+j][size(iden[size(iden0)-1+j])+1]=
2231                      intvec(iden0[size(iden0)][i][1],k);
2232               found=1;
2233               break;
2234            }
2235         }
2236         if(!found)
2237         {
2238//--- no match yet, maybe there are entries not corresponding to the
2239//--- initialization of the list -- collected in list repair
2240            if(!defined(repair))
2241            {
2242//--- no entries in repair, we add the very first one
2243               list repair;
2244               repair[1]=list(intvec(iden0[size(iden0)][i][1],k));
2245            }
2246            else
2247            {
2248//--- compare against repair, and add the item appropriately
2249//--- steps of comparison as before
2250               for(c=1;c<=size(repair);c++)
2251               {
2252                  for(d=1;d<=size(repair[c]);d++)
2253                  {
2254                     if(defined(opath)) {kill opath;}
2255                     def opath=imap(re[2][repair[c][d][1]],path);
2256                     b=0;
2257                     while(path[1,b+1]==opath[1,b+1])
2258                     {
2259                        b++;
2260                        if((b>ncols(path)-1)||(b>ncols(opath)-1)) break;
2261                     }
2262                     b=int(leadcoef(path[1,b]));
2263                     string tempstr="EList["+string(eval(repair[c][d][2]))
2264                                     +"]";
2265                     if(defined(id1)){kill id1;}
2266                     ideal id1=fetchInTree(re,repair[c][d][1],b,
2267                               iden0[size(iden0)][i][1],tempstr,iden0,1);
2268                     kill tempstr;
2269                     if((size(reduce(EList[k],std(id1)))==0)&&
2270                        (size(reduce(id1,std(EList[k])))==0))
2271                     {
2272                        repair[c][size(repair[c])+1]=intvec(iden0[size(iden0)][i][1],k);
2273                        break;
2274                     }
2275                  }
2276                  if(d<=size(repair[c]))
2277                  {
2278                     break;
2279                  }
2280               }
2281               if(c>size(repair))
2282               {
2283                  repair[size(repair)+1]=list(intvec(iden0[size(iden0)][i][1],k));
2284               }
2285            }
2286         }
2287      }
2288   }
2289   if(defined(repair))
2290   {
2291//--- there were further components, add them
2292      for(c=1;c<=size(repair);c++)
2293      {
2294         iden[size(iden)+1]=repair[c];
2295      }
2296      kill repair;
2297   }
2298//--- up to now only Q-irred components - not C-irred components !!!
2299   return(iden);
2300}
2301example
2302{"EXAMPLE:";
2303   echo = 2;
2304   ring R=0,(x,y,z),dp;
2305   ideal I=x2+y2+z11;
2306   list L=resolve(I);
2307   prepEmbDiv(L);
2308}
2309///////////////////////////////////////////////////////////////////////////////
2310static
2311proc decompEinX(list BO)
2312"Internal procedure - no help and no example available
2313"
2314{
2315//--- decomposition of exceptional divisor, non-embedded resolution.
2316//--- even a single exceptional divisor may be Q-reducible when considered
2317//--- as divisor on the strict transform
2318
2319//----------------------------------------------------------------------------
2320// Initialization
2321//----------------------------------------------------------------------------
2322   int i,j,k,de,contact;
2323   intmat interMat;
2324   list dcE,tmpList,prList,sa,nullList;
2325   string mpol,compList;
2326   def R=basering;
2327   ideal I;
2328//----------------------------------------------------------------------------
2329// pass to divisors on V(J) and throw away components already present as
2330// previous exceptional divisors
2331//----------------------------------------------------------------------------
2332   for(i=1;i<=size(BO[4]);i++)
2333   {
2334      I=BO[4][i]+BO[2];
2335      for(j=i+1;j<=size(BO[4]);j++)
2336      {
2337         sa=sat(I,BO[4][j]+BO[2]);
2338         if(sa[2])
2339         {
2340           I=sa[1];
2341         }
2342      }
2343//!!! Practical improvement - not yet implemented:
2344//!!!hier den Input besser aufbereiten (cf. J. Wahl's example)
2345//!!!I[1]=x(2)^15*y(2)^9+3*x(2)^10*y(2)^6+3*x(2)^5*y(2)^3+x(2)+1;
2346//!!!I[2]=x(2)^8*y(2)^6+y(0);
2347//!!!heuristisch die Ordnung so waehlen, dass y(0) im Prinzip eliminiert
2348//!!!wird.
2349//-----------------------------------------------------------------------------
2350// 1) decompose exceptional divisor (over Q)
2351// 2) check whether there are C-reducible Q-components
2352// 3) if necessary, find appropriate field extension of Q to decompose
2353// 4) in each chart collect information in list dcE and export it
2354//-----------------------------------------------------------------------------
2355      prList=primdecGTZ(I);
2356      for(j=1;j<=size(prList);j++)
2357      {
2358        tmpList=grad(prList[j][2]);
2359        de=tmpList[1];
2360        interMat=tmpList[2];
2361        mpol=tmpList[3];
2362        compList=tmpList[4];
2363        nullList=tmpList[5];
2364        contact=Kontakt(prList[j][1],BO[2]);
2365        tmpList=prList[j][2],de,contact,interMat,mpol,compList,nullList;
2366        prList[j]=tmpList;
2367      }
2368      dcE[i]=prList;
2369   }
2370   return(dcE);
2371}
2372//////////////////////////////////////////////////////////////////////////////
2373static
2374proc getMinpoly(poly p)
2375"Internal procedure - no help and no example available
2376"
2377{
2378//---assume that p is a polynomial in 2 variables and irreducible
2379//---over Q. Computes an irreducible polynomial mp in one variable
2380//---over Q such that p splits completely over the splitting field of mp
2381//---returns mp as a string
2382//---use a variant of the algorithm of S. Gao
2383  def R=basering;
2384  int i,j,k,a,b,m,n;
2385  intvec v;
2386  string mp="poly p=t-1;";
2387  list Li=string(1);
2388  list re=mp,Li,1;
2389
2390//---check which variables occur in p
2391  for(i=1;i<=nvars(basering);i++)
2392  {
2393    if(p!=subst(p,var(i),0)){v[size(v)+1]=i;}
2394  }
2395
2396//---the polynomial is constant
2397  if(size(v)==1){return(re);}
2398
2399//---the polynomial depends only on one variable or is homogeneous
2400//---in 2 variables
2401  if((size(v)==2)||((size(v)==3)&&(homog(p))))
2402  {
2403     if((size(v)==3)&&(homog(p)))
2404     {
2405        p=subst(p,var(v[3]),1);
2406     }
2407     ring Rhelp=0,var(v[2]),dp;
2408     poly p=imap(R,p);
2409     ring Shelp=0,t,dp;
2410     poly p=fetch(Rhelp,p);
2411     int de=deg(p);
2412     p=simplifyMinpoly(p);
2413     Li=getNumZeros(p);
2414     short=0;
2415     mp="poly p="+string(p)+";";
2416     re=mp,Li,de;
2417     setring R;
2418     return(re);
2419  }
2420  v=v[2..size(v)];
2421  if(size(v)>2){ERROR("getMinpoly:input depends on more then 2 variables");}
2422
2423//---the general case, the polynomial is considered as polynomial in x an y now
2424  ring T=0,(x,y),lp;
2425  ideal M,N;
2426  M[nvars(R)]=0;
2427  N[nvars(R)]=0;
2428  M[v[1]]=x;
2429  N[v[1]]=y;
2430  M[v[2]]=y;
2431  N[v[2]]=x;
2432  map phi=R,M;
2433  map psi=R,N;
2434  poly p=phi(p);
2435  poly q=psi(p);
2436  ring Thelp=(0,x),y,dp;
2437  poly p=imap(T,p);
2438  poly q=imap(T,q);
2439  n=deg(p);              //---the degree with respect to y
2440  m=deg(q);              //---the degree with respect to x
2441  setring T;
2442  ring A=0,(u(1..m*(n+1)),v(1..(m+1)*n),x,y,t),dp;
2443  poly f=imap(T,p);
2444  poly g;
2445  poly h;
2446  for(i=0;i<=m-1;i++)
2447  {
2448     for(j=0;j<=n;j++)
2449     {
2450        g=g+u(i*(n+1)+j+1)*x^i*y^j;
2451     }
2452  }
2453  for(i=0;i<=m;i++)
2454  {
2455     for(j=0;j<=n-1;j++)
2456     {
2457        h=h+v(i*n+j+1)*x^i*y^j;
2458     }
2459  }
2460  poly L=f*(diff(g,y)-diff(h,x))+h*diff(f,x)-g*diff(f,y);
2461//---according to the theory f is absolutely irreducible if and only if
2462//---L(g,h)=0 has no non-trivial solution g,h
2463//---(g=diff(f,x),h=diff(f,y) is always a solution)
2464//---therefore we compute a vector space basis of G
2465//---G={g in Q[x,y],deg_x(g)<m,|exist h, such that L(g,h)=0}
2466//---dim(G)=a is the number of factors of f in C[x,y]
2467  matrix M=coef(L,xy);
2468  ideal J=M[2,1..ncols(M)];
2469  option(redSB);
2470  J=std(J);
2471  option(noredSB);
2472  poly gred=reduce(g,J);
2473  ideal G;
2474  for(i=1;i<=m*(n+1);i++)
2475  {
2476    if(gred!=subst(gred,u(i),0))
2477    {
2478       G[size(G)+1]=subst(gred,u(i),1);
2479    }
2480  }
2481  for(i=1;i<=n*(m+1);i++)
2482  {
2483    if(gred!=subst(gred,v(i),0))
2484    {
2485       G[size(G)+1]=subst(gred,v(i),1);
2486    }
2487  }
2488  for(i=1;i<=m*(n+1);i++)
2489  {
2490     G=subst(G,u(i),0);
2491  }
2492  for(i=1;i<=n*(m+1);i++)
2493  {
2494     G=subst(G,v(i),0);
2495  }
2496//---the number of factors in C[x,y]
2497  a=size(G);
2498  for(i=1;i<=a;i++)
2499  {
2500     G[i]=simplify(G[i],1);
2501  }
2502  if(a==1)
2503  {
2504//---f is absolutely irreducible
2505    setring R;
2506    return(re);
2507  }
2508//---let g in G be any non-trivial element (g not in <diff(f,x)>)
2509//---according to the theory f=product over all c in C of the
2510//---gcd(f,g-c*diff(f,x))
2511//---let g_1,...,g_a be a basis of G and write
2512//---g*g_i=sum a_ij*g_j*diff(f,x)  mod f
2513//---let B=(a_ij) and ch=det(t*unitmat(a)-B) the characteristic
2514//---polynomial then the number of distinct irreducible factors
2515//---of gcd(f,g-c*diff(f,x)) in C[x,y] is equal to the multiplicity
2516//---of c as a root of ch.
2517//---in our special situation (f is irreducible over Q) ch should
2518//---be irreducible and the different roots of ch lead to the
2519//---factors of f, i.e. ch is the minpoly we are looking for
2520
2521  poly fh=homog(f,t);
2522//---homogenization is used to obtain a constant matrix using lift
2523  ideal Gh=homog(G,t);
2524  int dh,df;
2525  df=deg(fh);
2526  for(i=1;i<=a;i++)
2527  {
2528    if(deg(Gh[i])>dh){dh=deg(Gh[i]);}
2529  }
2530  for(i=1;i<=a;i++)
2531  {
2532    Gh[i]=t^(dh-deg(Gh[i]))*Gh[i];
2533  }
2534  ideal GF=simplify(diff(fh,x),1)*Gh,fh;
2535  poly ch;
2536  matrix LI;
2537  matrix B[a][a];
2538  matrix E=unitmat(a);
2539  poly gran;
2540  ideal fac;
2541  for(i=1;i<=a;i++)
2542  {
2543     LI=lift(GF,t^(df-1-dh)*Gh[i]*Gh);
2544     B=LI[1..a,1..a];
2545     ch=det(t*E-B);
2546//---irreducibility test
2547     fac=factorize(ch,1);
2548     if(deg(fac[1])==a)
2549     {
2550        ch=simplifyMinpoly(ch);
2551        Li=getNumZeros(ch);
2552        int de=deg(ch);
2553        short=0;
2554        mp="poly p="+string(ch)+";";
2555        re=mp,Li,de;
2556        setring R;
2557        return(re);
2558     }
2559  }
2560  ERROR("getMinpoly:not found:please send the example to the authors");
2561}
2562//////////////////////////////////////////////////////////////////////////////
2563static
2564proc getNumZeros(poly p)
2565"Internal procedure - no help and no example available
2566"
2567{
2568//--- compute numerically (!!!) the zeros of the minimal polynomial
2569  def R=basering;
2570  ring S=0,t,dp;
2571  poly p=imap(R,p);
2572  def L=laguerre_solve(p,30);
2573//!!! practical improvement:
2574//!!! testen ob die Nullstellen signifikant verschieden sind
2575//!!! und im Notfall Genauigkeit erhoehen
2576  list re;
2577  int i;
2578  for(i=1;i<=size(L);i++)
2579  {
2580    re[i]=string(L[i]);
2581  }
2582  setring R;
2583  return(re);
2584}
2585//////////////////////////////////////////////////////////////////////////////
2586static
2587proc simplifyMinpoly(poly p)
2588"Internal procedure - no help and no example available
2589"
2590{
2591//--- describe field extension in a simple way
2592   p=cleardenom(p);
2593   int n=int(leadcoef(p));
2594   int d=deg(p);
2595   int i,k;
2596   int re=1;
2597   number s=1;
2598
2599   list L=primefactors(n);
2600
2601   for(i=1;i<=size(L[1]);i++)
2602   {
2603      k=L[2][i] mod d;
2604      s=1/number((L[1][i])^(L[2][i]/d));
2605      if(!k){p=subst(p,t,s*t);}
2606   }
2607   p=cleardenom(p);
2608   n=int(leadcoef(subst(p,t,0)));
2609   L=primefactors(n);
2610   for(i=1;i<=size(L[1]);i++)
2611   {
2612      k=L[2][i] mod d;
2613      s=(L[1][i])^(L[2][i]/d);
2614      if(!k){p=subst(p,t,s*t);}
2615   }
2616   p=cleardenom(p);
2617   return(p);
2618}
2619///////////////////////////////////////////////////////////////////////////////
2620static
2621proc grad(ideal I)
2622"Internal procedure - no help and no example available
2623"
2624{
2625//--- computes the number of components over C
2626//--- for a prime ideal of height 1 over Q
2627  def R=basering;
2628  int n=nvars(basering);
2629  string mp="poly p=t-1;";
2630  string str=string(1);
2631  list zeroList=string(1);
2632  int i,j,k,l,d,e,c,mi;
2633  ideal Istd=std(I);
2634  intmat interMat;
2635  d=dim(Istd);
2636  if(d==-1){return(list(0,0,mp,str,zeroList));}
2637  if(d!=1){ERROR("ideal is not one-dimensional");}
2638  ideal Sloc=std(slocus(I));
2639  if(deg(Sloc[1])>0)
2640  {
2641//---This is only to test that in case of singularities we have only
2642//---one singular point which is a normal crossing
2643//---consider the different singular points
2644    ideal M;
2645    list pr=minAssGTZ(Sloc);
2646    if(size(pr)>1){ERROR("grad:more then one singular point");}
2647    for(l=1;l<=size(pr);l++)
2648    {
2649       M=std(pr[l]);
2650       d=vdim(M);
2651       if(d!=1)
2652       {
2653//---now we have to extend the field
2654          if(defined(S)){kill S;}
2655          ring S=0,x(1..n),lp;
2656          ideal M=fetch(R,M);
2657          ideal I=fetch(R,I);
2658          ideal jmap;
2659          map phi=S,maxideal(1);;
2660          ideal Mstd=std(M);
2661//---M has to be in general position with respect to lp, i.e.
2662//---vdim(M)=deg(M[1])
2663          poly p=Mstd[1];
2664          e=vdim(Mstd);
2665          while(e!=deg(p))
2666          {
2667             jmap=randomLast(100);
2668             phi=S,jmap;
2669             Mstd=std(phi(M));
2670             p=Mstd[1];
2671          }
2672          I=phi(I);
2673          kill phi;
2674//---now it is in general position an M[1] defines the field extension
2675//---Q[x]/M over Q
2676          ring Shelp=0,t,dp;
2677          ideal helpmap;
2678          helpmap[n]=t;
2679          map psi=S,helpmap;
2680          poly p=psi(p);
2681          ring T=(0,t),x(1..n),lp;
2682          poly p=imap(Shelp,p);
2683//---we are now in the polynomial ring over the field Q[x]/M
2684          minpoly=leadcoef(p);
2685          ideal M=imap(S,Mstd);
2686          M=M,var(n)-t;
2687          ideal I=fetch(S,I);
2688       }
2689//---we construct a map phi which maps M to maxideal(1)
2690       option(redSB);
2691       ideal Mstd=-simplify(std(M),1);
2692       option(noredSB);
2693       for(i=1;i<=n;i++)
2694       {
2695         Mstd=subst(Mstd,var(i),-var(i));
2696         M[n-i+1]=Mstd[i];
2697       }
2698       M=M[1..n];
2699//---go to the localization with respect to <x>
2700       if(d!=1)
2701       {
2702          ring Tloc=(0,t),x(1..n),ds;
2703          poly p=imap(Shelp,p);
2704          minpoly=leadcoef(p);
2705          ideal M=fetch(T,M);
2706          map phi=T,M;
2707       }
2708       else
2709       {
2710          ring Tloc=0,x(1..n),ds;
2711          ideal M=fetch(R,M);
2712          map phi=R,M;
2713       }
2714       ideal I=phi(I);
2715       ideal Istd=std(I);
2716       mi=mi+milnor(Istd);
2717       if(mi>l)
2718       {
2719          ERROR("grad:divisor is really singular");
2720       }
2721       setring R;
2722    }
2723  }
2724  intvec ind=indepSet(Istd,1)[1];
2725  for(i=1;i<=n;i++){if(ind[i]) break;}
2726//---the i-th variable is the independent one
2727  ring Shelp=0,x(1..n),dp;
2728  ideal I=fetch(R,I);
2729  if(defined(S)){kill S;}
2730  if(i==1){ring S=(0,x(1)),x(2..n),lp;}
2731  if(i==n){ring S=(0,x(n)),x(1..n-1),lp;}
2732  if((i!=1)&&(i!=n)){ring S=(0,x(i)),(x(1..i-1),x(i+1..n)),lp;}
2733//---I is zero-dimensional now
2734  ideal I=imap(Shelp,I);
2735  ideal Istd=std(I);
2736  ideal jmap;
2737  map phi;
2738  poly p=Istd[1];
2739  e=vdim(Istd);
2740  if(e==1)
2741  {
2742     setring R;
2743     str=string(I);
2744     list resi=1,interMat,mp,str,zeroList;
2745     return(resi);
2746  }
2747//---move I to general position with respect to lp
2748  if(e!=deg(p))
2749  {
2750     jmap=randomLast(5);
2751     phi=S,jmap;
2752     Istd=std(phi(I));
2753     p=Istd[1];
2754  }
2755  while(e!=deg(p))
2756  {
2757     jmap=randomLast(100);
2758     phi=S,jmap;
2759     Istd=std(phi(I));
2760     p=Istd[1];
2761  }
2762  setring Shelp;
2763  poly p=imap(S,p);
2764  list Q=getMinpoly(p);
2765  int de=Q[3];
2766  mp=Q[1];
2767//!!!diese Stelle effizienter machen
2768//!!!minAssGTZ vermeiden durch direkte Betrachtung von
2769//!!!p und mp und evtl. Quotientenbildung
2770//!!!bisher nicht zeitkritisch
2771  string Tesr="ring Tes=(0,t),("+varstr(R)+"),dp;";
2772  execute(Tesr);
2773  execute(mp);
2774  minpoly=leadcoef(p);
2775  ideal I=fetch(R,I);
2776  list pr=minAssGTZ(I);
2777  ideal allgEbene=randomLast(100)[nvars(basering)];
2778  int minpts=vdim(std(I+allgEbene));
2779  ideal tempi;
2780  j=1;
2781  for(i=1;i<=size(pr);i++)
2782  {
2783    tempi=std(pr[i]+allgEbene);
2784    if(vdim(tempi)<minpts)
2785    {
2786      minpts=vdim(tempi);
2787      j=i;
2788    }
2789  }
2790  tempi=pr[j];
2791  str=string(tempi);
2792  kill interMat;
2793  setring R;
2794  intmat interMat[de][de]=intersComp(str,mp,Q[2],str,mp,Q[2]);
2795  list resi=de,interMat,mp,str,Q[2];
2796  return(resi);
2797}
2798////////////////////////////////////////////////////////////////////////////
2799static
2800proc Kontakt(ideal I, ideal K)
2801"Internal procedure - no help and no example available
2802"
2803{
2804//---Let K be a prime ideal and I an ideal not contained in K
2805//---computes a maximalideal M=<x(1)-a1,...,x(n)-an>, ai in a field
2806//---extension of Q,  containing I+K and an integer a
2807//---such that in the localization of the polynomial ring with
2808//---respect to M the ideal I is not contained in K+M^a+1 but in M^a in
2809  def R=basering;
2810  int n=nvars(basering);
2811  int i,j,k,d,e;
2812  ideal J=std(I+K);
2813  if(dim(J)==-1){return(0);}
2814  ideal W;
2815//---choice of the maximal ideal M
2816  for(i=1;i<=n;i++)
2817  {
2818     W=std(J,var(i));
2819     d=dim(W);
2820     if(d==0) break;
2821  }
2822  i=1;k=2;
2823  while((d)&&(i<n))
2824  {
2825     W=std(J,var(i)+var(k));
2826     d=dim(W);
2827     if(k==n){i++;k=i;}
2828     if(k<n){k++;}
2829  }
2830  while(d)
2831  {
2832    W=std(J,randomid(maxideal(1))[1]);
2833    d=dim(W);
2834  }
2835//---now we have a collection om maximalideals and choose one with dim Q[x]/M
2836//---minimal
2837  list pr=minAssGTZ(W);
2838  d=vdim(std(pr[1]));
2839  k=1;
2840  for(i=2;i<=size(pr);i++)
2841  {
2842    if(d==1) break;
2843    e=vdim(std(pr[i]));
2844    if(e<d){k=i;d=e;}
2845  }
2846//---M is fixed now
2847//---if dim Q[x]/M =1 we localize at M
2848  ideal M=pr[k];
2849  if(d!=1)
2850  {
2851//---now we have to extend the field
2852     if(defined(S)){kill S;}
2853     ring S=0,x(1..n),lp;
2854     ideal M=fetch(R,M);
2855     ideal I=fetch(R,I);
2856     ideal K=fetch(R,K);
2857     ideal jmap;
2858     map phi=S,maxideal(1);;
2859     ideal Mstd=std(M);
2860//---M has to be in general position with respect to lp, i.e.
2861//---vdim(M)=deg(M[1])
2862     poly p=Mstd[1];
2863     e=vdim(Mstd);
2864     while(e!=deg(p))
2865     {
2866        jmap=randomLast(100);
2867        phi=S,jmap;
2868        Mstd=std(phi(M));
2869        p=Mstd[1];
2870     }
2871     I=phi(I);
2872     K=phi(K);
2873     kill phi;
2874//---now it is in general position an M[1] defines the field extension
2875//---Q[x]/M over Q
2876     ring Shelp=0,t,dp;
2877     ideal helpmap;
2878     helpmap[n]=t;
2879     map psi=S,helpmap;
2880     poly p=psi(p);
2881     ring T=(0,t),x(1..n),lp;
2882     poly p=imap(Shelp,p);
2883//---we are now in the polynomial ring over the field Q[x]/M
2884     minpoly=leadcoef(p);
2885     ideal M=imap(S,Mstd);
2886     M=M,var(n)-t;
2887     ideal I=fetch(S,I);
2888     ideal K=fetch(S,K);
2889  }
2890//---we construct a map phi which maps M to maxideal(1)
2891  option(redSB);
2892  ideal Mstd=-simplify(std(M),1);
2893  option(noredSB);
2894  for(i=1;i<=n;i++)
2895  {
2896    Mstd=subst(Mstd,var(i),-var(i));
2897    M[n-i+1]=Mstd[i];
2898  }
2899  M=M[1..n];
2900//---go to the localization with respect to <x>
2901  if(d!=1)
2902  {
2903     ring Tloc=(0,t),x(1..n),ds;
2904     poly p=imap(Shelp,p);
2905     minpoly=leadcoef(p);
2906     ideal M=fetch(T,M);
2907     map phi=T,M;
2908  }
2909  else
2910  {
2911     ring Tloc=0,x(1..n),ds;
2912     ideal M=fetch(R,M);
2913     map phi=R,M;
2914  }
2915  ideal K=phi(K);
2916  ideal I=phi(I);
2917//---compute the order of I in (Q[x]/M)[[x]]/K
2918  k=1;d=0;
2919  while(!d)
2920  {
2921     k++;
2922     d=size(reduce(I,std(maxideal(k)+K)));
2923  }
2924  setring R;
2925  return(k-1);
2926}
2927example
2928{"EXAMPLE:";
2929   echo = 2;
2930   ring r = 0,(x,y,z),dp;
2931   ideal I=x4+z4+1;
2932   ideal K=x+y2+z2;
2933   Kontakt(I,K);
2934}
2935//////////////////////////////////////////////////////////////////////////////
2936static
2937proc abstractNC(list BO)
2938"Internal procedure - no help and no example available
2939"
2940{
2941//--- check normal crossing property
2942//--- used for passing from embedded to non-embedded resolution
2943//----------------------------------------------------------------------------
2944// Initialization
2945//----------------------------------------------------------------------------
2946  int i,k,j,flag;
2947  list L;
2948  ideal J;
2949  if(dim(std(cent))>0){return(1);}
2950//----------------------------------------------------------------------------
2951// check each exceptional divisor on V(J)
2952//----------------------------------------------------------------------------
2953  for(i=1;i<=size(BO[4]);i++)
2954  {
2955    if(dim(std(BO[2]+BO[4][i]))>0)
2956    {
2957//--- really something to do
2958      J=radical(BO[4][i]+BO[2]);
2959      if(deg(std(slocus(J))[1])!=0)
2960      {
2961        if(!nodes(J))
2962        {
2963//--- really singular, not only nodes ==> not normal crossing
2964          return(0);
2965        }
2966      }
2967      for(k=1;k<=size(L);k++)
2968      {
2969//--- run through previously considered divisors
2970//--- we do not want to bother with the same one twice
2971         if((size(reduce(J,std(L[k])))==0)&&(size(reduce(L[k],std(J)))==0))
2972         {
2973//--- already considered this one
2974            flag=1;break;
2975         }
2976//--- drop previously considered exceptional divisors from the current one
2977         J=sat(J,L[k])[1];
2978         if(deg(std(J)[1])==0)
2979         {
2980//--- nothing remaining
2981            flag=1;break;
2982         }
2983      }
2984      if(flag==0)
2985      {
2986//--- add exceptional divisor to the list
2987         L[size(L)+1]=J;
2988      }
2989      flag=0;
2990    }
2991  }
2992//---------------------------------------------------------------------------
2993// check intersection properties between different exceptional divisors
2994//---------------------------------------------------------------------------
2995  for(k=1;k<size(L);k++)
2996  {
2997     for(i=k+1;i<=size(L);i++)
2998     {
2999        if(!nodes(intersect(L[k],L[i])))
3000        {
3001//--- divisors Ek and Ei do not meet in a node but in a singularity
3002//--- which is not allowed to occur ==> not normal crossing
3003           return(0);
3004        }
3005        for(j=i+1;j<=size(L);j++)
3006        {
3007           if(deg(std(L[i]+L[j]+L[k])[1])>0)
3008           {
3009//--- three divisors meet simultaneously ==> not normal crossing
3010              return(0);
3011           }
3012        }
3013     }
3014   }
3015//--- we reached this point ==> normal crossing
3016   return(1);
3017}
3018//////////////////////////////////////////////////////////////////////////////
3019static
3020proc nodes(ideal J)
3021"Internal procedure - no help and no example available
3022"
3023{
3024//--- check whether at most nodes occur as singularities
3025   ideal K=std(slocus(J));
3026   if(deg(K[1])==0){return(1);}
3027   if(dim(K)>0){return(0);}
3028   if(vdim(K)!=vdim(std(radical(K)))){return(0);}
3029   return(1);
3030}
3031//////////////////////////////////////////////////////////////////////////////
3032
3033proc intersectionDiv(list re)
3034"USAGE:   intersectionDiv(L);
3035@*        L = list of rings
3036ASSUME:   L is output of resolution of singularities
3037          (only case of isolated surface singularities)
3038COMPUTE:  intersection matrix and genera of the exceptional divisors
3039          (considered as curves on the strict transform)
3040RETURN:   list l, where
3041          l[1]: intersection matrix of exceptional divisors
3042          l[2]: intvec, genera of exceptional divisors
3043          l[3]: divisorList, encoding the identification of the divisors
3044EXAMPLE:  example intersectionDiv;  shows an example
3045"
3046{
3047//----------------------------------------------------------------------------
3048//--- Computes in case of surface singularities (non-embedded resolution):
3049//--- the intersection of the divisors (on the surface)
3050//--- assuming that re=resolve(J)
3051//----------------------------------------------------------------------------
3052   def R=basering;
3053//---Test whether we are in the irreducible surface case
3054   def S=re[2][1];
3055   setring S;
3056   BO[2]=BO[2]+BO[1];              // make sure we are living in the smooth W
3057   if(dim(std(BO[2]))!=2)
3058   {
3059     ERROR("The given original object is not a surface");
3060   }
3061   if(dim(std(slocus(BO[2])))>0)
3062   {
3063     ERROR("The given original object has non-isolated singularities.");
3064   }
3065   setring R;
3066//----------------------------------------------------------------------------
3067// Compute a non-embedded resolution from the given embedded one by
3068// dropping redundant trailing blow-ups
3069//----------------------------------------------------------------------------
3070   list resu,tmpiden,templist;
3071   intvec divcomp;
3072   int i,j,k,offset1,offset2,a,b,c,d,q,found;
3073//--- compute non-embedded resolution
3074   list abst=abstractR(re);
3075   intvec endiv=abst[1];
3076   intvec deleted=abst[2];
3077//--- identify the divisors in the various final charts
3078   list iden=collectDiv(re,deleted)[2];
3079                                    // list of final divisors
3080   list iden0=iden;                 // backup copy of iden for later use
3081
3082   iden=delete(iden,size(iden));    // drop list of endRings from iden
3083//---------------------------------------------------------------------------
3084// In iden, only the final charts should be listed, whereas iden0 contains
3085// everything.
3086//---------------------------------------------------------------------------
3087   for(i=1;i<=size(iden);i++)
3088   {
3089     k=size(iden[i]);
3090     tmpiden=iden[i];
3091     for(j=k;j>0;j--)
3092     {
3093        if(!endiv[iden[i][j][1]])
3094        {
3095//---not a final chart
3096           tmpiden=delete(tmpiden,j);
3097        }
3098     }
3099     if(size(tmpiden)==0)
3100     {
3101//--- oops, this divisor does not appear in final charts
3102        iden=delete(iden,i);
3103        continue;
3104     }
3105     else
3106     {
3107        iden[i]=tmpiden;
3108     }
3109   }
3110//---------------------------------------------------------------------------
3111// Even though the exceptional divisors were irreducible in the embedded
3112// case, they may very well have become reducible after intersection with
3113// the strict transform of the original object.
3114// ===> compute a decomposition for each divisor in each of the final charts
3115//      and change the entries of iden accordingly
3116// In particular, it is important to keep track of the identification of the
3117// components of the divisors in each of the charts
3118//---------------------------------------------------------------------------
3119   int n=size(iden);
3120   for(i=1;i<=size(re[2]);i++)
3121   {
3122     if(endiv[i])
3123     {
3124        def SN=re[2][i];
3125        setring SN;
3126        if(defined(dcE)){kill dcE;}
3127        list dcE=decompEinX(BO);       // decomposition of exceptional divisors
3128        export(dcE);
3129        setring R;
3130        kill SN;
3131     }
3132   }
3133   if(defined(tmpiden)){kill tmpiden;}
3134   list tmpiden=iden;
3135   for(i=1;i<=size(iden);i++)
3136   {
3137      for(j=size(iden[i]);j>0;j--)
3138      {
3139         def SN=re[2][iden[i][j][1]];
3140         setring SN;
3141         if(size(dcE[iden[i][j][2]])==1)
3142         {
3143           if(dcE[iden[i][j][2]][1][2]==0)
3144           {
3145             tmpiden[i]=delete(tmpiden[i],j);
3146           }
3147         }
3148         setring R;
3149         kill SN;
3150      }
3151   }
3152   for(i=size(tmpiden);i>0;i--)
3153   {
3154      if(size(tmpiden[i])==0)
3155      {
3156         tmpiden=delete(tmpiden,i);
3157      }
3158   }
3159   iden=tmpiden;
3160   kill tmpiden;
3161   list tmpiden;
3162//--- change entries of iden accordingly
3163   for(i=1;i<=size(iden);i++)
3164   {
3165//--- first set up new entries in iden if necessary - using the first chart
3166//--- in which we see the respective exceptional divisor
3167     if(defined(S)){kill S;}
3168     def S=re[2][iden[i][1][1]];
3169//--- considering first entry for i-th divisor
3170     setring S;
3171     a=size(dcE[iden[i][1][2]]);
3172     for(j=1;j<=a;j++)
3173     {
3174//--- reducible - add to the list considering each component as an exceptional
3175//--- divisor in its own right
3176        list tl;
3177        tl[1]=intvec(iden[i][1][1],iden[i][1][2],j);
3178        tmpiden[size(tmpiden)+1]=tl;
3179        kill tl;
3180     }
3181//--- now identify the components in the other charts w.r.t. the ones in the
3182//--- first chart which have already been added to the list
3183     for(j=2;j<=size(iden[i]);j++)
3184     {
3185//--- considering remaining entries for the same original divisor
3186       if(defined(S2)){kill S2;}
3187       def S2=re[2][iden[i][j][1]];
3188       setring S2;
3189//--- determine common parent of this ring and re[2][iden[i][1][1]]
3190       if(defined(opath)){kill opath;}
3191       def opath=imap(S,path);
3192       b=1;
3193       while(opath[1,b]==path[1,b])
3194       {
3195          b++;
3196          if((b>ncols(path))||(b>ncols(opath))) break;
3197       }
3198       if(defined(li1)){kill li1;}
3199       list li1;
3200//--- fetch the components we have considered in re[2][iden[i][1][1]]
3201//--- via the resolution tree
3202       for(k=1;k<=a;k++)
3203       {
3204          string tempstr="dcE["+string(eval(iden[i][1][2]))+"]["+string(k)+"][1]";
3205          if(defined(id1)){kill id1;}
3206          ideal id1=fetchInTree(re,iden[i][1][1],int(leadcoef(path[1,b-1])),
3207                      iden[i][j][1],tempstr,iden0,1);
3208          kill tempstr;
3209          li1[k]=radical(id1);        // for comparison only the geometric
3210                                      // object matters
3211          kill id1;
3212       }
3213//--- compare the components we have fetched with the components in the
3214//--- current ring
3215       for(k=1;k<=size(dcE[iden[i][j][2]]);k++)
3216       {
3217          found=0;
3218          for(b=1;b<=size(li1);b++)
3219          {
3220             if((size(reduce(li1[b],std(dcE[iden[i][j][2]][k][1])))==0)&&
3221               (size(reduce(dcE[iden[i][j][2]][k][1],std(li1[b]+BO[2])))==0))
3222             {
3223                li1[b]=ideal(1);
3224                tmpiden[size(tmpiden)-a+b][size(tmpiden[size(tmpiden)-a+b])+1]=
3225                       intvec(iden[i][j][1],iden[i][j][2],k);
3226                found=1;
3227                break;
3228             }
3229          }
3230          if(!found)
3231          {
3232            if(!defined(repair))
3233            {
3234               list repair;
3235               repair[1]=list(intvec(iden[i][j][1],iden[i][j][2],k));
3236            }
3237            else
3238            {
3239               for(c=1;c<=size(repair);c++)
3240               {
3241                  for(d=1;d<=size(repair[c]);d++)
3242                  {
3243                     if(defined(opath)) {kill opath;}
3244                     def opath=imap(re[2][repair[c][d][1]],path);
3245                     q=0;
3246                     while(path[1,q+1]==opath[1,q+1])
3247                     {
3248                        q++;
3249                        if((q>ncols(path)-1)||(q>ncols(opath)-1)) break;
3250                     }
3251                     q=int(leadcoef(path[1,q]));
3252                     string tempstr="dcE["+string(eval(repair[c][d][2]))+"]["+string(eval(repair[c][d][3]))+"][1]";
3253                     if(defined(id1)){kill id1;}
3254                     ideal id1=fetchInTree(re,repair[c][d][1],q,
3255                                  iden[i][j][1],tempstr,iden0,1);
3256                     kill tempstr;
3257//!!! sind die nicht schon radical?
3258                     id1=radical(id1);        // for comparison
3259                                              // only the geometric
3260                                              // object matters
3261                     if((size(reduce(dcE[iden[i][j][2]][k][1],std(id1+BO[2])))==0)&&
3262                        (size(reduce(id1+BO[2],std(dcE[iden[i][j][2]][k][1])))==0))
3263                     {
3264                       repair[c][size(repair[c])+1]=intvec(iden[i][j][1],iden[i][j][2],k);
3265                       break;
3266                     }
3267                  }
3268                  if(d<=size(repair[c]))
3269                  {
3270                     break;
3271                  }
3272               }
3273               if(c>size(repair))
3274               {
3275                  repair[size(repair)+1]=list(intvec(iden[i][j][1],iden[i][j][2],k));
3276               }
3277            }
3278         }
3279       }
3280     }
3281     if(defined(repair))
3282     {
3283       for(c=1;c<=size(repair);c++)
3284       {
3285          tmpiden[size(tmpiden)+1]=repair[c];
3286       }
3287       kill repair;
3288     }
3289   }
3290   setring R;
3291   for(i=size(tmpiden);i>0;i--)
3292   {
3293      if(size(tmpiden[i])==0)
3294      {
3295        tmpiden=delete(tmpiden,i);
3296        continue;
3297      }
3298   }
3299   iden=tmpiden;                      // store the modified divisor list
3300   kill tmpiden;                      // and clean up temporary objects
3301//---------------------------------------------------------------------------
3302// Now we have decomposed everything into irreducible components over Q,
3303// but over C there might still be some reducible ones left:
3304// Determine the number of components over C.
3305//---------------------------------------------------------------------------
3306   n=0;
3307   for(i=1;i<=size(iden);i++)
3308   {
3309      if(defined(S)) {kill S;}
3310      def S=re[2][iden[i][1][1]];
3311      setring S;
3312      divcomp[i]=ncols(dcE[iden[i][1][2]][iden[i][1][3]][4]);
3313          // number of components of the Q-irreducible curve dcE[iden[i][1][2]]
3314      n=n+divcomp[i];
3315      setring R;
3316   }
3317//---------------------------------------------------------------------------
3318// set up the entries Inters[i,j] , i!=j, in the intersection matrix:
3319// we have to compute the intersection of the exceptional divisors (over C)
3320//    i.e. we have to work in over appropriate algebraic extension of Q.
3321// (1) plug the intersection matrices of the components of the same Q-irred.
3322//     divisor into the correct position in the intersection matrix
3323// (2) for comparison of Ei,k and Ej,l move to a chart where both divisors
3324//     are present, fetch the components from the very first chart containing
3325//     the respective divisor and then compare by using intersComp
3326// (4) put the result into the correct position in the integer matrix Inters
3327//---------------------------------------------------------------------------
3328//--- some initialization
3329   int comPai,comPaj;
3330   intvec v,w;
3331   intmat Inters[n][n];
3332//--- run through all Q-irreducible exceptional divisors
3333   for(i=1;i<=size(iden);i++)
3334   {
3335      if(divcomp[i]>1)
3336      {
3337//--- (1) put the intersection matrix for Ei,k with Ei,l into the correct place
3338         for(k=1;k<=size(iden[i]);k++)
3339         {
3340            if(defined(tempmat)){kill tempmat;}
3341            intmat tempmat=imap(re[2][iden[i][k][1]],dcE)[iden[i][k][2]][iden[i][k][3]][4];
3342            if(size(ideal(tempmat))!=0)
3343            {
3344               Inters[i+offset1..(i+offset1+divcomp[i]-1),
3345                      i+offset1..(i+offset1+divcomp[i]-1)]=
3346                       tempmat[1..nrows(tempmat),1..ncols(tempmat)];
3347               break;
3348            }
3349            kill tempmat;
3350         }
3351      }
3352      offset2=offset1+divcomp[i]-1;
3353//--- set up the components over C of the i-th exceptional divisor
3354      if(defined(S)){kill S;}
3355      def S=re[2][iden[i][1][1]];
3356      setring S;
3357      if(defined(idlisti)) {kill idlisti;}
3358      list idlisti;
3359      idlisti[1]=dcE[iden[i][1][2]][iden[i][1][3]][6];
3360      export(idlisti);
3361      setring R;
3362//--- run through the remaining exceptional divisors and check whether they
3363//--- have a chart in common with the i-th divisor
3364      for(j=i+1;j<=size(iden);j++)
3365      {
3366         kill templist;
3367         list templist;
3368         for(k=1;k<=size(iden[i]);k++)
3369         {
3370            intvec tiv2=findInIVList(1,iden[i][k][1],iden[j]);
3371            if(size(tiv2)!=1)
3372            {
3373//--- tiv2[1] is a common chart for the divisors i and j
3374              tiv2[4..6]=iden[i][k];
3375              templist[size(templist)+1]=tiv2;
3376            }
3377            kill tiv2;
3378         }
3379         if(size(templist)==0)
3380         {
3381//--- the two (Q-irred) divisors do not appear in any chart simultaneously
3382            offset2=offset2+divcomp[j]-1;
3383            j++;
3384            continue;
3385         }
3386         for(k=1;k<=size(templist);k++)
3387         {
3388            if(defined(S)) {kill S;}
3389//--- set up the components over C of the j-th exceptional divisor
3390            def S=re[2][iden[j][1][1]];
3391            setring S;
3392            if(defined(idlistj)) {kill idlistj;}
3393            list idlistj;
3394            idlistj[1]=dcE[iden[j][1][2]][iden[j][1][3]][6];
3395            export(idlistj);
3396            if(defined(opath)){kill opath;}
3397            def opath=imap(re[2][templist[k][1]],path);
3398            comPaj=1;
3399            while(opath[1,comPaj]==path[1,comPaj])
3400            {
3401              comPaj++;
3402              if((comPaj>ncols(opath))||(comPaj>ncols(path))) break;
3403            }
3404            comPaj=int(leadcoef(path[1,comPaj-1]));
3405            setring R;
3406            kill S;
3407            def S=re[2][iden[i][1][1]];
3408            setring S;
3409            if(defined(opath)){kill opath;}
3410            def opath=imap(re[2][templist[k][1]],path);
3411            comPai=1;
3412            while(opath[1,comPai]==path[1,comPai])
3413            {
3414               comPai++;
3415               if((comPai>ncols(opath))||(comPai>ncols(path))) break;
3416            }
3417            comPai=int(leadcoef(opath[1,comPai-1]));
3418            setring R;
3419            kill S;
3420            def S=re[2][templist[k][1]];
3421            setring S;
3422            if(defined(il)) {kill il;}
3423            if(defined(jl)) {kill jl;}
3424            if(defined(str1)) {kill str1;}
3425            if(defined(str2)) {kill str2;}
3426            string str1="idlisti";
3427            string str2="idlistj";
3428            attrib(str1,"algext",imap(re[2][iden[i][1][1]],dcE)[iden[i][1][2]][iden[i][1][3]][5]);
3429            attrib(str2,"algext",imap(re[2][iden[j][1][1]],dcE)[iden[j][1][2]][iden[j][1][3]][5]);
3430            list il=fetchInTree(re,iden[i][1][1],comPai,
3431                                templist[k][1],str1,iden0,1);
3432            list jl=fetchInTree(re,iden[j][1][1],comPaj,
3433                                templist[k][1],str2,iden0,1);
3434            list nulli=imap(re[2][iden[i][1][1]],dcE)[iden[i][1][2]][iden[i][1][3]][7];
3435            list nullj=imap(re[2][iden[j][1][1]],dcE)[iden[j][1][2]][iden[j][1][3]][7];
3436            string mpi=imap(re[2][iden[i][1][1]],dcE)[iden[i][1][2]][iden[i][1][3]][5];
3437            string mpj=imap(re[2][iden[j][1][1]],dcE)[iden[j][1][2]][iden[j][1][3]][5];
3438            if(defined(tintMat)){kill tintMat;}
3439            intmat tintMat=intersComp(il[1],mpi,nulli,jl[1],mpj,nullj);
3440            kill mpi;
3441            kill mpj;
3442            kill nulli;
3443            kill nullj;
3444            for(a=1;a<=divcomp[i];a++)
3445            {
3446               for(b=1;b<=divcomp[j];b++)
3447               {
3448                 if(tintMat[a,b]!=0)
3449                 {
3450                    Inters[i+offset1+a-1,j+offset2+b-1]=tintMat[a,b];
3451                    Inters[j+offset2+b-1,i+offset1+a-1]=tintMat[a,b];
3452                 }
3453               }
3454            }
3455         }
3456         offset2=offset2+divcomp[j]-1;
3457      }
3458      offset1=offset1+divcomp[i]-1;
3459   }
3460   Inters=addSelfInter(re,Inters,iden,iden0,endiv);
3461   intvec GenusIden;
3462
3463   list tl_genus;
3464   a=1;
3465   for(i=1;i<=size(iden);i++)
3466   {
3467      tl_genus=genus_E(re,iden0,iden[i][1]);
3468      for(j=1;j<=tl_genus[2];j++)
3469      {
3470        GenusIden[a]=tl_genus[1];
3471        a++;
3472      }
3473   }
3474
3475   list retlist=Inters,GenusIden,iden,divcomp;
3476   return(retlist);
3477}
3478example
3479{"EXAMPLE:";
3480   echo = 2;
3481   ring r = 0,(x(1..3)),dp(3);
3482   ideal J=x(3)^5+x(2)^4+x(1)^3+x(1)*x(2)*x(3);
3483   list re=resolve(J);
3484   list di=intersectionDiv(re);
3485   di;
3486
3487}
3488//////////////////////////////////////////////////////////////////////////////
3489static
3490proc intersComp(string str1,
3491                string mp1,
3492                list null1,
3493                string str2,
3494                string mp2,
3495                list null2)
3496"Internal procedure - no help and no example available
3497"
3498{
3499//--- format of input
3500//--- str1 : ideal (over field extension 1)
3501//--- mp1  : minpoly of field extension 1
3502//--- null1: numerical zeros of minpoly
3503//--- str2 : ideal (over field extension 2)
3504//--- mp2  : minpoly of field extension 2
3505//--- null2: numerical zeros of minpoly
3506
3507//--- determine intersection matrix of the C-components defined by the input
3508
3509//---------------------------------------------------------------------------
3510// Initialization
3511//---------------------------------------------------------------------------
3512  int ii,jj,same;
3513  def R=basering;
3514  intmat InterMat[size(null1)][size(null2)];
3515  ring ringst=0,(t,s),dp;
3516//---------------------------------------------------------------------------
3517// Add new variables s and t and compare the minpolys and ideals
3518// to find out whether they are identical
3519//---------------------------------------------------------------------------
3520  def S=R+ringst;
3521  setring S;
3522  if((mp1==mp2)&&(str1==str2))
3523  {
3524    same=1;
3525  }
3526//--- define first Q-component/C-components, substitute t by s
3527  string tempstr="ideal id1="+str1+";";
3528  execute(tempstr);
3529  execute(mp1);
3530  id1=subst(id1,t,s);
3531  poly q=subst(p,t,s);
3532  kill p;
3533//--- define second Q-component/C-components
3534  tempstr="ideal id2="+str2+";";
3535  execute(tempstr);
3536  execute(mp2);
3537//--- do the intersection
3538  ideal interId=id1+id2+ideal(p)+ideal(q);
3539  if(same)
3540  {
3541    interId=quotient(interId,t-s);
3542  }
3543  interId=std(interId);
3544//--- refine the comparison by passing to each of the numerical zeros
3545//--- of the two minpolys
3546  ideal stid=nselect(interId,1..nvars(R));
3547  ring compl_st=complex,(s,t),dp;
3548  def stid=imap(S,stid);
3549  ideal tempid,tempid2;
3550  for(ii=1;ii<=size(null1);ii++)
3551  {
3552    tempstr="number numi="+null1[ii]+";";
3553    execute(tempstr);
3554    tempid=subst(stid,s,numi);
3555    kill numi;
3556    for(jj=1;jj<=size(null2);jj++)
3557    {
3558       tempstr="number numj="+null2[jj]+";";
3559       execute(tempstr);
3560       tempid2=subst(tempid,t,numj);
3561       kill numj;
3562       if(size(tempid2)==0)
3563       {
3564         InterMat[ii,jj]=1;
3565       }
3566    }
3567  }
3568//--- sanity check; as both Q-components were Q-irreducible,
3569//--- summation over all entries of a single row must lead to the same
3570//--- result, no matter which row is chosen
3571//--- dito for the columns
3572  int cou,cou1;
3573  for(ii=1;ii<=ncols(InterMat);ii++)
3574  {
3575    cou=0;
3576    for(jj=1;jj<=nrows(InterMat);jj++)
3577    {
3578      cou=cou+InterMat[jj,ii];
3579    }
3580    if(ii==1){cou1=cou;}
3581    if(cou1!=cou){ERROR("intersComp:matrix has wrong entries");}
3582  }
3583  for(ii=1;ii<=nrows(InterMat);ii++)
3584  {
3585    cou=0;
3586    for(jj=1;jj<=ncols(InterMat);jj++)
3587    {
3588      cou=cou+InterMat[ii,jj];
3589    }
3590    if(ii==1){cou1=cou;}
3591    if(cou1!=cou){ERROR("intersComp:matrix has wrong entries");}
3592  }
3593  return(InterMat);
3594}
3595/////////////////////////////////////////////////////////////////////////////
3596static
3597proc addSelfInter(list re,intmat Inters,list iden,list iden0,intvec endiv)
3598"Internal procedure - no help and no example available
3599"
3600{
3601//---------------------------------------------------------------------------
3602// Initialization
3603//---------------------------------------------------------------------------
3604   def R=basering;
3605   int i,j,k,l,a,b;
3606   int n=size(iden);
3607   intvec v,w;
3608   list satlist;
3609   def T=re[2][1];
3610   setring T;
3611   poly p;
3612   p=var(1);  //any linear form will do,
3613              //but this one is most convenient
3614   ideal F=ideal(p);
3615//----------------------------------------------------------------------------
3616// lift linear form to every end ring, determine the multiplicity of
3617// the exceptional divisors and store it in Flist
3618//----------------------------------------------------------------------------
3619   list templist;
3620   intvec tiv;
3621   for(i=1;i<=size(endiv);i++)
3622   {
3623     if(endiv[i]==1)
3624     {
3625        kill v;
3626        intvec v;
3627        a=0;
3628        if(defined(S)) {kill S;}
3629        def S=re[2][i];
3630        setring S;
3631        map resi=T,BO[5];
3632        ideal F=resi(F)+BO[2];
3633        ideal Ftemp=F;
3634        list Flist;
3635        if(defined(satlist)){kill satlist;}
3636        list satlist;
3637        for(a=1;a<=size(dcE);a++)
3638        {
3639           for(b=1;b<=size(dcE[a]);b++)
3640           {
3641              Ftemp=sat(Ftemp,dcE[a][b][1])[1];
3642           }
3643        }
3644        F=sat(F,Ftemp)[1];
3645        Flist[1]=Ftemp;
3646        Ftemp=1;
3647        list pr=primdecGTZ(F);
3648        v[size(pr)]=0;
3649        for(j=1;j<=size(pr);j++)
3650        {
3651          for(a=1;a<=size(dcE);a++)
3652          {
3653             if(j==1)
3654             {
3655               kill tiv;
3656               intvec tiv;
3657               tiv[size(dcE[a])]=0;
3658               templist[a]=tiv;
3659               if(v[j]==1)
3660               {
3661                 a++;
3662                 continue;
3663               }
3664             }
3665             if(dcE[a][1][2]==0)
3666             {
3667                a++;
3668                continue;
3669             }
3670             for(b=1;b<=size(dcE[a]);b++)
3671             {
3672                if((size(reduce(dcE[a][b][1],std(pr[j][2])))==0)&&
3673                   (size(reduce(pr[j][2],std(dcE[a][b][1])))==0))
3674                {
3675                  templist[a][b]=Vielfachheit(pr[j][1],pr[j][2]);
3676                  v[j]=1;
3677                  break;
3678                }
3679             }
3680             if((v[j]==1)&&(j>1)) break;
3681          }
3682        }
3683        kill v;
3684        intvec v;
3685        Flist[2]=templist;
3686     }
3687   }
3688//-----------------------------------------------------------------------------
3689// Now set up all the data:
3690// 1. run through all exceptional divisors in iden and determine the
3691//    coefficients c_i of the divisor of F.  ===> civ
3692// 2. determine the intersection locus of F^bar and the Ei and from this data
3693//    the F^bar.Ei . ===> intF
3694//-----------------------------------------------------------------------------
3695   intvec civ;
3696   intvec intF;
3697   intF[ncols(Inters)]=0;
3698   int offset,comPa,ncomp,vd;
3699   for(i=1;i<=size(iden);i++)
3700   {
3701      ncomp=0;
3702      for(j=1;j<=size(iden[i]);j++)
3703      {
3704        if(defined(S)) {kill S;}
3705        def S=re[2][iden[i][j][1]];
3706        setring S;
3707        if((size(civ)<i+offset+1)&&
3708           (((Flist[2][iden[i][j][2]][iden[i][j][3]])!=0)||(j==size(iden[i]))))
3709        {
3710           ncomp=ncols(dcE[iden[i][j][2]][iden[i][j][3]][4]);
3711           for(k=1;k<=ncomp;k++)
3712           {
3713              civ[i+offset+k]=Flist[2][iden[i][j][2]][iden[i][j][3]];
3714              if(deg(std(slocus(dcE[iden[i][j][2]][iden[i][j][3]][1]))[1])>0)
3715              {
3716                   civ[i+offset+k]=civ[i+k];
3717              }
3718           }
3719        }
3720        if(defined(interId)) {kill interId;}
3721        ideal interId=dcE[iden[i][j][2]][iden[i][j][3]][1]+Flist[1];
3722        if(defined(interList)) {kill interList;}
3723        list interList;
3724        interList[1]=string(interId);
3725        interList[2]=ideal(0);
3726        export(interList);
3727        if(defined(doneId)) {kill doneId;}
3728        if(defined(tempId)) {kill tempId;}
3729        ideal doneId=ideal(1);
3730        if(defined(dl)) {kill dl;}
3731        list dl;
3732        for(k=1;k<j;k++)
3733        {
3734           if(defined(St)) {kill St;}
3735           def St=re[2][iden[i][k][1]];
3736           setring St;
3737           if(defined(str)){kill str;}
3738           string str="interId="+interList[1]+";";
3739           execute(str);
3740           if(deg(std(interId)[1])==0)
3741           {
3742             setring S;
3743             k++;
3744             continue;
3745           }
3746           setring S;
3747           if(defined(opath)) {kill opath;}
3748           def opath=imap(re[2][iden[i][k][1]],path);
3749           comPa=1;
3750           while(opath[1,comPa]==path[1,comPa])
3751           {
3752              comPa++;
3753              if((comPa>ncols(path))||(comPa>ncols(opath))) break;
3754           }
3755           comPa=int(leadcoef(path[1,comPa-1]));
3756           if(defined(str)) {kill str;}
3757           string str="interList";
3758           attrib(str,"algext","poly p=t-1;");
3759           dl=fetchInTree(re,iden[i][k][1],comPa,iden[i][j][1],str,iden0,1);
3760           if(defined(tempId)){kill tempId;}
3761           str="ideal tempId="+dl[1]+";";
3762           execute(str);
3763           doneId=intersect(doneId,tempId);
3764           str="interId="+interList[1]+";";
3765           execute(str);
3766           interId=sat(interId,doneId)[1];
3767           interList[1]=string(interId);
3768        }
3769        interId=std(interId);
3770        if(dim(interId)>0)
3771        {
3772           "oops, intersection not a set of points";
3773           ~;
3774        }
3775        vd=vdim(interId);
3776        if(vd>0)
3777        {
3778          for(k=i+offset;k<=i+offset+ncomp-1;k++)
3779          {
3780             intF[k]=intF[k]+(vd/ncomp);
3781          }
3782        }
3783      }
3784      offset=size(civ)-i-1;
3785   }
3786   if(defined(tiv)){kill tiv;}
3787   intvec tiv=civ[2..size(civ)];
3788   civ=tiv;
3789   kill tiv;
3790//-----------------------------------------------------------------------------
3791// Using the F_total= sum c_i Ei + F^bar, the intersection matrix Inters and
3792// the f^bar.Ei, determine the selfintersection numbers of the Ei from the
3793// equation F_total.Ei=0 and store it in the diagonal of Inters.
3794//-----------------------------------------------------------------------------
3795   intvec diag=Inters*civ+intF;
3796   for(i=1;i<=size(diag);i++)
3797   {
3798      Inters[i,i]=-diag[i]/civ[i];
3799   }
3800   return(Inters);
3801}
3802//////////////////////////////////////////////////////////////////////////////
3803static
3804proc invSort(list re, list #)
3805"Internal procedure - no help and no example available
3806"
3807{
3808  int i,j,k,markier,EZeiger,offset;
3809  intvec v,e;
3810  intvec deleted;
3811  if(size(#)>0)
3812  {
3813     deleted=#[1];
3814  }
3815  else
3816  {
3817    deleted[size(re[2])]=0;
3818  }
3819  list LE,HI;
3820  def R=basering;
3821//----------------------------------------------------------------------------
3822// Go through all rings
3823//----------------------------------------------------------------------------
3824  for(i=1;i<=size(re[2]);i++)
3825  {
3826     if(deleted[i]){i++;continue}
3827     def S=re[2][i];
3828     setring S;
3829//----------------------------------------------------------------------------
3830// Determine Invariant
3831//----------------------------------------------------------------------------
3832     if((size(BO[3])==size(BO[9]))||(size(BO[3])==size(BO[9])+1))
3833     {
3834        if(defined(merk2)){kill merk2;}
3835        intvec merk2;
3836        EZeiger=0;
3837        for(j=1;j<=size(BO[9]);j++)
3838        {
3839          offset=0;
3840          if(BO[7][j]==-1)
3841          {
3842             BO[7][j]=size(BO[4])-EZeiger;
3843          }
3844          for(k=EZeiger+1;(k<=EZeiger+BO[7][j])&&(k<=size(BO[4]));k++)
3845          {
3846             if(BO[6][k]==2)
3847             {
3848                offset++;
3849             }
3850          }
3851          EZeiger=EZeiger+BO[7][1];
3852          merk2[3*j-2]=BO[3][j];
3853          merk2[3*j-1]=BO[9][j]-offset;
3854          if(size(invSat[2])>j)
3855          {
3856            merk2[3*j]=-invSat[2][j];
3857          }
3858          else
3859          {
3860            if(j<size(BO[9]))
3861            {
3862               "!!!!!problem with invSat";~;
3863            }
3864          }
3865        }
3866        if((size(BO[3])>size(BO[9])))
3867        {
3868          merk2[size(merk2)+1]=BO[3][size(BO[3])];
3869        }
3870        if((size(merk2)%3)==0)
3871        {
3872          intvec tintvec=merk2[1..size(merk2)-1];
3873          merk2=tintvec;
3874          kill tintvec;
3875        }
3876     }
3877     else
3878     {
3879         ERROR("This situation should not occur, please send the example
3880                 to the authors.");
3881     }
3882//----------------------------------------------------------------------------
3883// Save invariant describing current center as an object in this ring
3884// We also store information on the intersection with the center and the
3885// exceptional divisors
3886//----------------------------------------------------------------------------
3887     cent=std(cent);
3888     kill e;
3889     intvec e;
3890     for(j=1;j<=size(BO[4]);j++)
3891     {
3892        if(size(reduce(BO[4][j],std(cent+BO[1])))==0)
3893        {
3894           e[j]=1;
3895        }
3896        else
3897        {
3898           e[j]=0;
3899        }
3900     }
3901     if(size(ideal(merk2))==0)
3902     {
3903        markier=1;
3904     }
3905     if((size(merk2)%3==0)&&(merk2[size(merk2)]==0))
3906     {
3907       intvec blabla=merk2[1..size(merk2)-1];
3908       merk2=blabla;
3909       kill blabla;
3910     }
3911     if(defined(invCenter)){kill invCenter;}
3912     list invCenter=cent,merk2,e;
3913     export invCenter;
3914//----------------------------------------------------------------------------
3915// Insert it into correct place in the list
3916//----------------------------------------------------------------------------
3917     if(i==1)
3918     {
3919       if(!markier)
3920       {
3921         HI=intvec(merk2[1]+1),intvec(1);
3922       }
3923       else
3924       {
3925         HI=intvec(778),intvec(1);   // some really large integer
3926                                     // will be changed at the end!!!
3927       }
3928       LE[1]=HI;
3929       i++;
3930       setring R;
3931       kill S;
3932       continue;
3933     }
3934     if(markier==1)
3935     {
3936       if(i==2)
3937       {
3938         HI=intvec(777),intvec(2);   // same really large integer-1
3939         LE[2]=HI;
3940         i++;
3941         setring R;
3942         kill S;
3943         continue;
3944       }
3945       else
3946       {
3947         if(ncols(path)==2)
3948         {
3949           LE[2][2][size(LE[2][2])+1]=i;
3950           i++;
3951           setring R;
3952           kill S;
3953           continue;
3954         }
3955         else
3956         {
3957           markier=0;
3958         }
3959       }
3960     }
3961     j=1;
3962     def SOld=re[2][int(leadcoef(path[1,ncols(path)]))];
3963     setring SOld;
3964     merk2=invCenter[2];
3965     setring S;
3966     kill SOld;
3967     while(merk2<LE[j][1])
3968     {
3969        j++;
3970        if(j>size(LE)) break;
3971     }
3972     HI=merk2,intvec(i);
3973     if(j<=size(LE))
3974     {
3975        if(merk2>LE[j][1])
3976        {
3977          LE=insert(LE,HI,j-1);
3978        }
3979        else
3980        {
3981           while((merk2==LE[j][1])&&(size(merk2)<size(LE[j][1])))
3982           {
3983              j++;
3984              if(j>size(LE)) break;
3985           }
3986           if(j<=size(LE))
3987           {
3988              if((merk2!=LE[j][1])||(size(merk2)!=size(LE[j][1])))
3989              {
3990                LE=insert(LE,HI,j-1);
3991              }
3992              else
3993              {
3994                LE[j][2][size(LE[j][2])+1]=i;
3995              }
3996           }
3997           else
3998           {
3999              LE[size(LE)+1]=HI;
4000           }
4001        }
4002     }
4003     else
4004     {
4005        LE[size(LE)+1]=HI;
4006     }
4007     setring R;
4008     kill S;
4009  }
4010  if((LE[1][1]==intvec(778)) && (size(LE)>2))
4011  {
4012     LE[1][1]=intvec(LE[3][1][1]+2);     // by now we know what 'sufficiently
4013     LE[2][1]=intvec(LE[3][1][1]+1);     // large' is
4014  }
4015  return(LE);
4016}
4017example
4018{"EXAMPLE:";
4019   echo = 2;
4020   ring r = 0,(x(1..3)),dp(3);
4021   ideal J=x(1)^3-x(1)*x(2)^3+x(3)^2;
4022   list re=resolve(J,1);
4023   list di=invSort(re);
4024   di;
4025}
4026/////////////////////////////////////////////////////////////////////////////
4027static
4028proc addToRE(intvec v,int x,list RE)
4029"Internal procedure - no help and no example available
4030"
4031{
4032//--- auxilliary procedure for collectDiv,
4033//--- inserting an entry at the correct place
4034   int i=1;
4035   while(i<=size(RE))
4036   {
4037      if(v==RE[i][1])
4038      {
4039         RE[i][2][size(RE[i][2])+1]=x;
4040         return(RE);
4041      }
4042      if(v>RE[i][1])
4043      {
4044         list templist=v,intvec(x);
4045         RE=insert(RE,templist,i-1);
4046         return(RE);
4047      }
4048      i++;
4049   }
4050   list templist=v,intvec(x);
4051   RE=insert(RE,templist,size(RE));
4052   return(RE);
4053}
4054////////////////////////////////////////////////////////////////////////////
4055
4056proc collectDiv(list re,list #)
4057"USAGE:   collectDiv(L);
4058@*        L = list of rings
4059ASSUME:   L is output of resolution of singularities
4060COMPUTE:  list representing the identification of the exceptional divisors
4061          in the various charts
4062RETURN:   list l, where
4063          l[1]: intmat, entry k in position i,j implies BO[4][j] of chart i
4064                is divisor k (if k!=0)
4065                if k==0, no divisor corresponding to i,j
4066          l[2]: list ll, where each entry of ll is a list of intvecs
4067                entry i,j in list ll[k] implies BO[4][j] of chart i
4068                is divisor k
4069          l[3]: list L
4070EXAMPLE:  example collectDiv;   shows an example
4071"
4072{
4073//------------------------------------------------------------------------
4074// Initialization
4075//------------------------------------------------------------------------
4076  int i,j,k,l,m,maxk,maxj,mPa,oPa,interC,pa,ignoreL,iTotal;
4077  int mLast,oLast=1,1;
4078  intvec deleted;
4079//--- sort the rings by the invariant which controlled the last of the
4080//--- exceptional divisors
4081  if(size(#)>0)
4082  {
4083     deleted=#[1];
4084  }
4085  else
4086  {
4087    deleted[size(re[2])]=0;
4088  }
4089  list LE=invSort(re,deleted);
4090  list LEtotal=LE;
4091  intmat M[size(re[2])][size(re[2])];
4092  intvec invar,tempiv;
4093  def R=basering;
4094  list divList;
4095  list RE,SE;
4096  intvec myEi,otherEi,tempe;
4097  int co=2;
4098
4099  while(size(LE)>0)
4100  {
4101//------------------------------------------------------------------------
4102// Run through the sorted list LE whose entries are lists containing
4103// the invariant and the numbers of all rings corresponding to it
4104//------------------------------------------------------------------------
4105     for(i=co;i<=size(LE);i++)
4106     {
4107//--- i==1 in first iteration:
4108//--- the original ring which did not arise from a blow-up
4109//--- hence there are no exceptional divisors to be identified there ;
4110
4111//------------------------------------------------------------------------
4112// For each fixed value of the invariant, run through all corresponding
4113// rings
4114//------------------------------------------------------------------------
4115        for(l=1;l<=size(LE[i][2]);l++)
4116        {
4117           if(defined(S)){kill S;}
4118           def S=re[2][LE[i][2][l]];
4119           setring S;
4120           if(size(BO[4])>maxj){maxj=size(BO[4]);}
4121//--- all exceptional divisors, except the last one, were previously
4122//--- identified - hence we can simply inherit the data from the parent ring
4123           for(j=1;j<size(BO[4]);j++)
4124           {
4125              if(deg(std(BO[4][j])[1])>0)
4126              {
4127                k=int(leadcoef(path[1,ncols(path)]));
4128                k=M[k,j];
4129                if(k==0)
4130                {
4131                   RE=addToRE(LE[i][1],LE[i][2][l],RE);
4132                   ignoreL=1;
4133                   break;
4134                }
4135                M[LE[i][2][l],j]=k;
4136                tempiv=LE[i][2][l],j;
4137                divList[k][size(divList[k])+1]=tempiv;
4138              }
4139           }
4140          if(ignoreL){ignoreL=0;l++;continue;}
4141//----------------------------------------------------------------------------
4142// In the remaining part of the procedure, the identification of the last
4143// exceptional divisor takes place.
4144// Step 1: check whether there is a previously considered ring with the
4145//         same parent; if this is the case, we can again inherit the data
4146// Step 1':check whether the parent had a stored center which it then used
4147//         in this case, we are dealing with an additional component of this
4148//         divisor: store it in the integer otherComp
4149// Step 2: if no appropriate ring was found in step 1, we check whether
4150//         there is a previously considered ring, in the parent of which
4151//         the center intersects the same exceptional divisors as the center
4152//         in our parent.
4153//         if such a ring does not exist: new exceptional divisor
4154//         if it exists: see below
4155//----------------------------------------------------------------------------
4156           if(path[1,ncols(path)-1]==0)
4157           {
4158//--- current ring originated from very first blow-up
4159//--- hence exceptional divisor is the first one
4160              M[LE[i][2][l],1]=1;
4161              if(size(divList)>0)
4162              {
4163                 divList[1][size(divList[1])+1]=intvec(LE[i][2][l],j);
4164              }
4165              else
4166              {
4167                 divList[1]=list(intvec(LE[i][2][l],j));
4168              }
4169              l++;
4170              continue;
4171           }
4172           if(l==1)
4173           {
4174              list TE=addToRE(LE[i][1],1,SE);
4175              if(size(TE)!=size(SE))
4176              {
4177//--- new value of invariant hence new exceptional divisor
4178                 SE=TE;
4179                 divList[size(divList)+1]=list(intvec(LE[i][2][l],j));
4180                 M[LE[i][2][l],j]=size(divList);
4181              }
4182              kill TE;
4183           }
4184           for(k=1;k<=size(LEtotal);k++)
4185           {
4186              if(LE[i][1]==LEtotal[k][1])
4187              {
4188                 iTotal=k;
4189                 break;
4190              }
4191           }
4192//--- Step 1
4193           k=1;
4194           while(LEtotal[iTotal][2][k]<LE[i][2][l])
4195           {
4196              if(defined(tempPath)){kill tempPath;}
4197              def tempPath=imap(re[2][LEtotal[iTotal][2][k]],path);
4198              if(tempPath[1,ncols(tempPath)]==path[1,ncols(path)])
4199              {
4200//--- Same parent, hence we inherit our data
4201                 m=size(imap(re[2][LEtotal[iTotal][2][k]],BO)[4]);
4202                 m=M[LEtotal[iTotal][2][k],m];
4203                 if(m==0)
4204                 {
4205                    RE=addToRE(LE[i][1],LE[i][2][l],RE);
4206                    ignoreL=1;
4207                    break;
4208                 }
4209                 M[LE[i][2][l],j]=m;
4210                 tempiv=LE[i][2][l],j;
4211                 divList[m][size(divList[m])+1]=tempiv;
4212                 break;
4213              }
4214              k++;
4215              if(k>size(LEtotal[iTotal][2])) {break;}
4216           }
4217           if(ignoreL){ignoreL=0;l++;continue;}
4218//--- Step 1', if necessary
4219           if(M[LE[i][2][l],j]==0)
4220           {
4221             int savedCent;
4222             def SPa1=re[2][int(leadcoef(path[1,ncols(path)]))];
4223                       // parent ring
4224             setring SPa1;
4225             if(size(BO)>9)
4226             {
4227                if(size(BO[10])>0)
4228                {
4229                   savedCent=1;
4230                }
4231             }
4232             if(!savedCent)
4233             {
4234                def SPa2=re[2][int(leadcoef(path[1,ncols(path)]))];
4235                map lMa=SPa2,lastMap;
4236                       // map leading from grandparent to parent
4237                list transBO=lMa(BO);
4238                       // actually we only need BO[10], but this is an
4239                       // object not a name
4240                list tempsat;
4241                if(size(transBO)>9)
4242                {
4243//--- there were saved centers
4244                   while((k<=size(transBO[10])) & (savedCent==0))
4245                   {
4246                      tempsat=sat(transBO[10][k][1],BO[4][size(BO[4])]);
4247                      if(deg(tempsat[1][1])!=0)
4248                      {
4249//--- saved center can be seen in this affine chart
4250                        if((size(reduce(tempsat[1],std(cent)))==0) &&
4251                           (size(reduce(cent,tempsat[1]))==0))
4252                        {
4253//--- this was the saved center which was used
4254                           savedCent=1;
4255                        }
4256                      }
4257                      k++;
4258                   }
4259                }
4260                kill lMa;          // clean up temporary objects
4261                kill tempsat;
4262                kill transBO;
4263             }
4264             setring S;         // back to the ring which we want to consider
4265             if(savedCent==1)
4266             {
4267               vector otherComp;
4268               otherComp[M[int(leadcoef(path[1,ncols(path)])),size(BO[4])-1]]
4269                        =1;
4270             }
4271             kill savedCent;
4272             if (defined(SPa2)){kill SPa2;}
4273             kill SPa1;
4274           }
4275//--- Step 2, if necessary
4276           if(M[LE[i][2][l],j]==0)
4277           {
4278//--- we are not done after step 1 and 2
4279              pa=int(leadcoef(path[1,ncols(path)]));  // parent ring
4280              tempe=imap(re[2][pa],invCenter)[3];     // intersection there
4281              kill myEi;
4282              intvec myEi;
4283              for(k=1;k<=size(tempe);k++)
4284              {
4285                if(tempe[k]==1)
4286                {
4287//--- center meets this exceptional divisor
4288                   myEi[size(myEi)+1]=M[pa,k];
4289                   mLast=k;
4290                }
4291              }
4292//--- ring in which the last divisor we meet is new-born
4293              mPa=int(leadcoef(path[1,mLast+2]));
4294              k=1;
4295              while(LEtotal[iTotal][2][k]<LE[i][2][l])
4296              {
4297//--- perform the same preparations for the ring we want to compare with
4298                 if(defined(tempPath)){kill tempPath;}
4299                 def tempPath=imap(re[2][LEtotal[iTotal][2][k]],path);
4300                                                          // its ancestors
4301                 tempe=imap(re[2][int(leadcoef(tempPath[1,ncols(tempPath)]))],
4302                         invCenter)[3];                   // its intersections
4303                 kill otherEi;
4304                 intvec otherEi;
4305                 for(m=1;m<=size(tempe);m++)
4306                 {
4307                   if(tempe[m]==1)
4308                   {
4309//--- its center meets this exceptional divisor
4310                     otherEi[size(otherEi)+1]
4311                          =M[int(leadcoef(tempPath[1,ncols(tempPath)])),m];
4312                     oLast=m;
4313                   }
4314                 }
4315                 if(myEi!=otherEi)
4316                 {
4317//--- not the same center because of intersection properties with the
4318//--- exceptional divisor
4319                    k++;
4320                    if(k>size(LEtotal[iTotal][2]))
4321                    {
4322                      break;
4323                    }
4324                    else
4325                    {
4326                      continue;
4327                    }
4328                 }
4329//----------------------------------------------------------------------------
4330// Current situation:
4331// 1. the last exceptional divisor could not be identified by simply
4332//    considering its parent
4333// 2. it could not be proved to be a new one by considering its intersections
4334//    with previous exceptional divisors
4335//----------------------------------------------------------------------------
4336                 if(defined(bool1)) { kill bool1;}
4337                 int bool1=
4338                       compareE(re,LE[i][2][l],LEtotal[iTotal][2][k],divList);
4339                 if(bool1)
4340                 {
4341//--- found some non-empty intersection
4342                    if(bool1==1)
4343                    {
4344//--- it is really the same exceptional divisor
4345                       m=size(imap(re[2][LEtotal[iTotal][2][k]],BO)[4]);
4346                       m=M[LEtotal[iTotal][2][k],m];
4347                       if(m==0)
4348                       {
4349                          RE=addToRE(LE[i][1],LE[i][2][l],RE);
4350                          ignoreL=1;
4351                          break;
4352                       }
4353                       M[LE[i][2][l],j]=m;
4354                       tempiv=LE[i][2][l],j;
4355                       divList[m][size(divList[m])+1]=tempiv;
4356                       break;
4357                    }
4358                    else
4359                    {
4360                       m=size(imap(re[2][LEtotal[iTotal][2][k]],BO)[4]);
4361                       m=M[LEtotal[iTotal][2][k],m];
4362                       if(m!=0)
4363                       {
4364                          otherComp[m]=1;
4365                       }
4366                    }
4367                 }
4368                 k++;
4369                 if(k>size(LEtotal[iTotal][2]))
4370                 {
4371                   break;
4372                 }
4373              }
4374              if(ignoreL){ignoreL=0;l++;continue;}
4375              if( M[LE[i][2][l],j]==0)
4376              {
4377                 divList[size(divList)+1]=list(intvec(LE[i][2][l],j));
4378                 M[LE[i][2][l],j]=size(divList);
4379              }
4380           }
4381           setring R;
4382           kill S;
4383        }
4384     }
4385     LE=RE;
4386     co=1;
4387     kill RE;
4388     list RE;
4389  }
4390//----------------------------------------------------------------------------
4391// Add the strict transform to the list of divisors at the last place
4392// and clean up M
4393//----------------------------------------------------------------------------
4394//--- add strict transform
4395  for(i=1;i<=size(re[2]);i++)
4396  {
4397     if(defined(S)){kill S;}
4398     def S=re[2][i];
4399     setring S;
4400     if(size(reduce(cent,std(BO[2])))==0)
4401     {
4402        tempiv=i,0;
4403        RE[size(RE)+1]=tempiv;
4404     }
4405     setring R;
4406  }
4407  divList[size(divList)+1]=RE;
4408//--- drop trailing zero-columns of M
4409  intvec iv0;
4410  iv0[nrows(M)]=0;
4411  for(i=ncols(M);i>0;i--)
4412  {
4413    if(intvec(M[1..nrows(M),i])!=iv0) break;
4414  }
4415  intmat N[nrows(M)][i];
4416  for(i=1;i<=ncols(N);i++)
4417  {
4418    N[1..nrows(M),i]=M[1..nrows(M),i];
4419  }
4420  kill M;
4421  intmat M=N;
4422  list retlist=cleanUpDiv(re,M,divList);
4423  return(retlist);
4424}
4425example
4426{"EXAMPLE:";
4427   echo = 2;
4428   ring R=0,(x,y,z),dp;
4429   ideal I=xyz+x4+y4+z4;
4430//we really need to blow up curves even if the generic point of
4431//the curve the total transform is n.c.
4432//this occurs here in r[2][5]
4433   list re=resolve(I);
4434   list di=collectDiv(re);
4435   di[1];
4436   di[2];
4437}
4438//////////////////////////////////////////////////////////////////////////////
4439static
4440proc cleanUpDiv(list re,intmat M,list divList)
4441"Internal procedure - no help and no example available
4442"
4443{
4444//--- It may occur that two different entries of invSort coincide on the
4445//--- first part up to the last entry of the shorter one. In this case
4446//--- exceptional divisors may appear in both entries of the invSort-list.
4447//--- To correct this, we now compare the final collection of Divisors
4448//--- for coinciding ones.
4449   int i,j,k,a,oPa,mPa,comPa,mdim,odim;
4450   def R=basering;
4451   for(i=1;i<=size(divList)-2;i++)
4452   {
4453      if(defined(Sm)){kill Sm;}
4454      def Sm=re[2][divList[i][1][1]];
4455      setring Sm;
4456      mPa=int(leadcoef(path[1,ncols(path)]));
4457      if(defined(SmPa)){kill SmPa;}
4458      def SmPa=re[2][mPa];
4459      setring SmPa;
4460      mdim=dim(std(BO[1]+cent));
4461      setring Sm;
4462      if(mPa==1)
4463      {
4464//--- very first divisor originates exactly from the first blow-up
4465//--- there cannot be any mistake here
4466         i++;
4467         continue;
4468      }
4469      for(j=i+1;j<=size(divList)-1;j++)
4470      {
4471         setring Sm;
4472         for(k=1;k<=size(divList[j]);k++)
4473         {
4474            if(size(findInIVList(1,divList[j][k][1],divList[i]))>1)
4475            {
4476//--- same divisor cannot appear twice in the same chart
4477               k=-1;
4478               break;
4479            }
4480         }
4481         if(k==-1)
4482         {
4483            j++;
4484            if(j>size(divList)-1) break;
4485            continue;
4486         }
4487         if(defined(opath)){kill opath;}
4488         def opath=imap(re[2][divList[j][1][1]],path);
4489         oPa=int(leadcoef(opath[1,ncols(opath)]));
4490         if(defined(SoPa)){kill SoPa;}
4491         def SoPa=re[2][oPa];
4492         setring SoPa;
4493         odim=dim(std(BO[1]+cent));
4494         setring Sm;
4495         if(mdim!=odim)
4496         {
4497//--- different dimension ==> cannot be same center
4498            j++;
4499            if(j>size(divList)-1) break;
4500            continue;
4501         }
4502         comPa=1;
4503         while(path[1,comPa]==opath[1,comPa])
4504         {
4505           comPa++;
4506           if((comPa>ncols(path))||(comPa>ncols(opath))) break;
4507         }
4508         comPa=int(leadcoef(path[1,comPa-1]));
4509         if(defined(SPa)){kill SPa;}
4510         def SPa=re[2][mPa];
4511         setring SPa;
4512         if(defined(tempIdE)){kill tempIdE;}
4513         ideal tempIdE=fetchInTree(re,oPa,comPa,mPa,"cent",divList);
4514         if((size(reduce(cent,std(tempIdE)))!=0)||
4515            (size(reduce(tempIdE,std(cent)))!=0))
4516         {
4517//--- it is not the same divisor!
4518            j++;
4519            if(j>size(divList))
4520            {
4521               break;
4522            }
4523            else
4524            {
4525               continue;
4526            }
4527         }
4528         for(k=1;k<=size(divList[j]);k++)
4529         {
4530//--- append the entries of the j-th divisor (which is actually also the i-th)
4531//--- to the i-th divisor
4532            divList[i][size(divList[i])+1]=divList[j][k];
4533         }
4534         divList=delete(divList,j);  //kill obsolete entry from the list
4535         for(k=1;k<=nrows(M);k++)
4536         {
4537            for(a=1;a<=ncols(M);a++)
4538            {
4539               if(M[k,a]==j)
4540               {
4541//--- j-th divisor is actually the i-th one
4542                  M[k,a]=i;
4543               }
4544               if(M[k,a]>j)
4545               {
4546//--- index j was deleted from the list ==> all subsequent indices dropped by
4547//--- one
4548                  M[k,a]=M[k,a]-1;
4549               }
4550            }
4551         }
4552         j--;                        //do not forget to consider new j-th entry
4553      }
4554   }
4555   setring R;
4556   list retlist=M,divList;
4557   return(retlist);
4558}
4559/////////////////////////////////////////////////////////////////////////////
4560static
4561proc findTrans(ideal Z, ideal E, list notE, list #)
4562"Internal procedure - no help and no example available
4563"
4564{
4565//---Auxilliary procedure for fetchInTree!
4566//---Assume E prime ideal, Z+E eqidimensional,
4567//---ht(E)+r=ht(Z+E). Compute  P=<p[1],...,p[r]> in Z+E, and polynomial f,
4568//---such that radical(Z+E)=radical((E+P):f)
4569   int i,j,d,e;
4570   ideal Estd=std(E);
4571//!!! alternative to subsequent line:
4572//!!!           ideal Zstd=std(radical(Z+E));
4573   ideal Zstd=std(Z+E);
4574   ideal J=1;
4575   if(size(#)>0)
4576   {
4577      J=#[1];
4578   }
4579   if(deg(Zstd[1])==0){return(list(ideal(1),poly(1)));}
4580   for(i=1;i<=size(notE);i++)
4581   {
4582      notE[i]=std(notE[i]);
4583   }
4584   ideal Zred=simplify(reduce(Z,Estd),2);
4585   if(size(Zred)==0){Z,Estd;~;ERROR("Z is contained in E");}
4586   ideal P,Q,Qstd;
4587   Q=Estd;
4588   attrib(Q,"isSB",1);
4589   d=dim(Estd);
4590   e=dim(Zstd);
4591   for(i=1;i<=size(Zred);i++)
4592   {
4593      Qstd=std(Q,Zred[i]);
4594      if(dim(Qstd)<d)
4595      {
4596         d=dim(Qstd);
4597         P[size(P)+1]=Zred[i];
4598         Q=Qstd;
4599         attrib(Q,"isSB",1);
4600         if(d==e) break;
4601      }
4602   }
4603   list pr=minAssGTZ(E+P);
4604   list sr=minAssGTZ(J+P);
4605   i=0;
4606   Q=1;
4607   list qr;
4608
4609   while(i<size(pr))
4610   {
4611      i++;
4612      Qstd=std(pr[i]);
4613      Zred=simplify(reduce(Zstd,Qstd),2);
4614      if(size(Zred)==0)
4615      {
4616        qr[size(qr)+1]=pr[i];
4617        pr=delete(pr,i);
4618        i--;
4619      }
4620      else
4621      {
4622         Q=intersect(Q,pr[i]);
4623      }
4624   }
4625   i=0;
4626   while(i<size(sr))
4627   {
4628      i++;
4629      Qstd=std(sr[i]+E);
4630      Zred=simplify(reduce(Zstd,Qstd),2);
4631      if((size(Zred)!=0)||(dim(Qstd)!=dim(Zstd)))
4632      {
4633        Q=intersect(Q,sr[i]);
4634      }
4635   }
4636   poly f;
4637   for(i=1;i<=size(Q);i++)
4638   {
4639      f=Q[i];
4640      for(e=1;e<=size(qr);e++)
4641      {
4642         if(reduce(f,std(qr[e]))==0){f=0;break;}
4643      }
4644      for(j=1;j<=size(notE);j++)
4645      {
4646         if(reduce(f,notE[j])==0){f=0; break;}
4647      }
4648      if(f!=0) break;
4649   }
4650   i=0;
4651   while(f==0)
4652   {
4653      i++;
4654      f=randomid(Q)[1];
4655      for(e=1;e<=size(qr);e++)
4656      {
4657         if(reduce(f,std(qr[e]))==0){f=0;break;}
4658      }
4659      for(j=1;j<=size(notE);j++)
4660      {
4661         if(reduce(f,notE[j])==0){f=0; break;}
4662      }
4663      if(f!=0) break;
4664      if(i>20)
4665      {
4666         ~;
4667         ERROR("findTrans:Hier ist was faul");
4668      }
4669   }
4670
4671   list resu=P,f;
4672   return(resu);
4673}
4674/////////////////////////////////////////////////////////////////////////////
4675static
4676proc compareE(list L, int m, int o, list DivL)
4677"Internal procedure - no help and no example available
4678"
4679{
4680//----------------------------------------------------------------------------
4681// We want to compare the divisors BO[4][size(BO[4])] of the rings
4682// L[2][m] and L[2][o].
4683// In the initialization step, we collect all necessary data from those
4684// those rings. In particular, we determine at what point (in the resolution
4685// history) the branches for L[2][m] and L[2][o] were separated, denoting
4686// the corresponding ring indices by mPa, oPa and comPa.
4687//----------------------------------------------------------------------------
4688   def R=basering;
4689   int i,j,k,len;
4690
4691//-- find direct parents and branching point in resolution history
4692   matrix tpm=imap(L[2][m],path);
4693   matrix tpo=imap(L[2][o],path);
4694   int m1,o1=int(leadcoef(tpm[1,ncols(tpm)])),
4695             int(leadcoef(tpo[1,ncols(tpo)]));
4696   while((i<ncols(tpo)) && (i<ncols(tpm)))
4697   {
4698     if(tpm[1,i+1]!=tpo[1,i+1]) break;
4699     i++;
4700   }
4701   int branchpos=i;
4702   int comPa=int(leadcoef(tpm[1,branchpos]));  // last common ancestor
4703//----------------------------------------------------------------------------
4704// simple checks to save us some work in obvious cases
4705//----------------------------------------------------------------------------
4706   if((comPa==m1)||(comPa==o1))
4707   {
4708//--- one is in the history of the other ==> they cannot give rise
4709//---                                        to the same divisor
4710      return(0);
4711   }
4712   def T=L[2][o1];
4713   setring T;
4714   int dimCo1=dim(std(cent+BO[1]));
4715   def S=L[2][m1];
4716   setring S;
4717   int dimCm1=dim(std(cent+BO[1]));
4718   if(dimCm1!=dimCo1)
4719   {
4720//--- centers do not have same dimension ==> they cannot give rise
4721//---                                        to the same divisor
4722      return(0);
4723   }
4724//----------------------------------------------------------------------------
4725// fetch the center via the tree for comparison
4726//----------------------------------------------------------------------------
4727   if(defined(invLocus0)) {kill invLocus0;}
4728   ideal invLocus0=fetchInTree(L,o1,comPa,m1,"cent",DivL);
4729             // blow down from L[2][o1] to L[2][comPa] and then up to L[2][m1]
4730   if(deg(std(invLocus0+invCenter[1]+BO[1])[1])!=0)
4731   {
4732     setring R;
4733     return(int(1));
4734   }
4735   if(size(BO)>9)
4736   {
4737     for(i=1;i<=size(BO[10]);i++)
4738     {
4739       if(deg(std(invLocus0+BO[10][i][1]+BO[1])[1])!=0)
4740       {
4741         if(dim(std(BO[10][i][1]+BO[1])) >
4742              dim(std(invLocus0+BO[10][i][1]+BO[1])))
4743         {
4744           ERROR("Internal Error: Please send this example to the authors.");
4745         }
4746         setring R;
4747         return(int(2));
4748       }
4749     }
4750   }
4751   setring R;
4752   return(int(0));
4753//----------------------------------------------------------------------------
4754// Return-Values:
4755//        TRUE (=1) if the exceptional divisors coincide,
4756//        TRUE (=2) if the exceptional divisors originate from different
4757//                  components of the same center
4758//        FALSE (=0) otherwise
4759//----------------------------------------------------------------------------
4760}
4761//////////////////////////////////////////////////////////////////////////////
4762
4763proc fetchInTree(list L,
4764                 int o1,
4765                 int comPa,
4766                 int m1,
4767                 string idname,
4768                 list DivL,
4769                 list #);
4770"Internal procedure - no help and no example available
4771"
4772{
4773//----------------------------------------------------------------------------
4774// Initialization and Sanity Checks
4775//----------------------------------------------------------------------------
4776   int i,j,k,m,branchPos,inJ,exception;
4777   string algext;
4778//--- we need to be in L[2][m1]
4779   def R=basering;
4780   ideal test_for_the_same_ring=-77;
4781   def Sm1=L[2][m1];
4782   setring Sm1;
4783   if(!defined(test_for_the_same_ring))
4784   {
4785//--- we are not in L[2][m1]
4786      ERROR("basering has to coincide with L[2][m1]");
4787   }
4788   else
4789   {
4790//--- we are in L[2][m1]
4791      kill test_for_the_same_ring;
4792   }
4793//--- non-embedded case?
4794   if(size(#)>0)
4795   {
4796      inJ=1;
4797   }
4798//--- do parameter values make sense?
4799   if(comPa<1)
4800   {
4801     ERROR("Common Parent should at least be the first ring!");
4802   }
4803//--- do we need to pass to an algebraic field extension of Q?
4804   if(typeof(attrib(idname,"algext"))=="string")
4805   {
4806      algext=attrib(idname,"algext");
4807   }
4808//--- check wheter comPa is in the history of m1
4809//--- same test for o1 can be done later on (on the fly)
4810   if(m1==comPa)
4811   {
4812      j=1;
4813      i=ncols(path)+1;
4814   }
4815   else
4816   {
4817      for(i=1;i<=ncols(path);i++)
4818      {
4819        if(int(leadcoef(path[1,i]))==comPa)
4820        {
4821//--- comPa occurs in the history
4822           j=1;
4823           break;
4824        }
4825      }
4826   }
4827   branchPos=i;
4828   if(j==0)
4829   {
4830     ERROR("L[2][comPa] not in history of L[2][m1]!");
4831   }
4832//----------------------------------------------------------------------------
4833// Blow down ideal "idname" from L[2][o1] to L[2][comPa], where the latter
4834// is assumed to be the common parent of L[2][o1] and L[2][m1]
4835//----------------------------------------------------------------------------
4836   if(size(algext)>0)
4837   {
4838//--- size(algext)>0: case of algebraic extension of base field
4839      if(defined(tstr)){kill tstr;}
4840      string tstr="ring So1=(0,t),("+varstr(L[2][o1])+"),("+ordstr(L[2][o1])+");";
4841      execute(tstr);
4842      setring So1;
4843      execute(algext);
4844      minpoly=leadcoef(p);
4845      if(defined(id1)) { kill id1; }
4846      if(defined(id2)) { kill id2; }
4847      if(defined(idlist)) { kill idlist; }
4848      execute("int bool2=defined("+idname+");");
4849      if(bool2==0)
4850      {
4851        execute("list ttlist=imap(L[2][o1],"+idname+");");
4852      }
4853      else
4854      {
4855        execute("list ttlist="+idname+";");
4856      }
4857      kill bool2;
4858      def BO=imap(L[2][o1],BO);
4859      def path=imap(L[2][o1],path);
4860      def lastMap=imap(L[2][o1],lastMap);
4861      ideal id2=1;
4862      if(defined(notE)){kill notE;}
4863      list notE;
4864      intvec nE;
4865      list idlist;
4866      for(i=1;i<=size(ttlist);i++)
4867      {
4868         if((i==size(ttlist))&&(typeof(ttlist[i])!="string")) break;
4869         execute("ideal tid="+ttlist[i]+";");
4870         idlist[i]=list(tid,ideal(1),nE);
4871         kill tid;
4872      }
4873   }
4874   else
4875   {
4876//--- size(algext)==0: no algebraic extension of base needed
4877      def So1=L[2][o1];
4878      setring So1;
4879      if(defined(id1)) { kill id1; }
4880      if(defined(id2)) { kill id2; }
4881      if(defined(idlist)) { kill idlist; }
4882      execute("ideal id1="+idname+";");
4883      if(deg(std(id1)[1])==0)
4884      {
4885//--- problems with findTrans if id1 is empty set
4886//!!! todo: also correct in if branch!!!
4887         setring R;
4888         return(ideal(1));
4889      }
4890     // id1=radical(id1);
4891      ideal id2=1;
4892      list idlist;
4893      if(defined(notE)){kill notE;}
4894      list notE;
4895      intvec nE;
4896      idlist[1]=list(id1,id2,nE);
4897   }
4898   if(defined(tli)){kill tli;}
4899   list tli;
4900   if(defined(id1)) { kill id1; }
4901   if(defined(id2)) { kill id2; }
4902   ideal id1;
4903   ideal id2;
4904   if(defined(Etemp)){kill Etemp;}
4905   ideal Etemp;
4906   for(m=1;m<=size(idlist);m++)
4907   {
4908//!!! Duplicate Block!!! All changes also needed below!!!
4909//!!! no subprocedure due to large data overhead!!!
4910//--- run through all ideals to be fetched
4911      id1=idlist[m][1];
4912      id2=idlist[m][2];
4913      nE=idlist[m][3];
4914      for(i=branchPos-1;i<=size(BO[4]);i++)
4915      {
4916//--- run through all relevant exceptional divisors
4917        if(size(reduce(BO[4][i],std(id1+BO[1])))==0)
4918        {
4919//--- V(id1) is contained in except. div. i in this chart
4920           if(size(reduce(id1,std(BO[4][i])))!=0)
4921           {
4922//--- V(id1) does not equal except. div. i of this chart
4923             Etemp=BO[4][i];
4924             if(npars(basering)>0)
4925             {
4926//--- we are in an algebraic extension of the base field
4927                if(defined(prtemp)){kill prtemp;}
4928                list prtemp=minAssGTZ(BO[4][i]);  // C-comp. of except. div.
4929                j=1;
4930                if(size(prtemp)>1)
4931                {
4932//--- more than 1 component
4933                  Etemp=ideal(1);
4934                  for(j=1;j<=size(prtemp);j++)
4935                  {
4936//--- find correct component
4937                     if(size(reduce(prtemp[j],std(id1)))==0)
4938                     {
4939                        Etemp=prtemp[j];
4940                        break;
4941                     }
4942                  }
4943                  if(deg(std(Etemp)[1])==0)
4944                  {
4945                    ERROR("fetchInTree:something wrong in field extension");
4946                  }
4947                }
4948                prtemp=delete(prtemp,j); // remove this comp. from list
4949                while(size(prtemp)>1)
4950                {
4951//--- collect all the others into prtemp[1]
4952                  prtemp[1]=intersect(prtemp[1],prtemp[size(prtemp)]);
4953                  prtemp=delete(prtemp,size(prtemp));
4954                }
4955             }
4956//--- determine tli[1] and tli[2] such that
4957//--- V(id1) \cap D(id2) = V(tli[1]) \cap D(tli[2]) \cap BO[4][i]
4958//--- inside V(BO[1]) (and if necessary inside V(BO[1]+BO[2]))
4959             if(inJ)
4960             {
4961                tli=findTrans(id1+BO[2]+BO[1],Etemp,notE,BO[2]);
4962             }
4963             else
4964             {
4965                tli=findTrans(id1+BO[1],Etemp,notE);
4966             }
4967             if(npars(basering)>0)
4968             {
4969//--- in algebraic extension: make sure we stay outside the other components
4970                if(size(prtemp)>0)
4971                {
4972                   for(j=1;j<=ncols(prtemp[1]);j++)
4973                   {
4974//--- find the (univariate) generator of prtemp[1] which is the remaining
4975//--- factor from the factorization over the extension field
4976                      if(size(reduce(prtemp[1][j],std(id1)))>0)
4977                      {
4978                         tli[2]=tli[2]*prtemp[1][j];
4979                      }
4980                   }
4981                }
4982             }
4983           }
4984           else
4985           {
4986//--- V(id1) equals except. div. i of this chart
4987             tli[1]=ideal(0);
4988             tli[2]=ideal(1);
4989           }
4990           id1=tli[1];
4991           id2=id2*tli[2];
4992           notE[size(notE)+1]=BO[4][i];
4993           for(j=1;j<=size(DivL);j++)
4994           {
4995              if(inIVList(intvec(o1,i),DivL[j]))
4996              {
4997                 nE[size(nE)+1]=j;
4998                 break;
4999              }
5000           }
5001           if(size(nE)<size(notE))
5002           {
5003              ERROR("fetchInTree: divisor not found in divL");
5004           }
5005        }
5006        idlist[m][1]=id1;
5007        idlist[m][2]=id2;
5008        idlist[m][3]=nE;
5009      }
5010//!!! End of Duplicate Block !!!!
5011   }
5012   if(o1>1)
5013   {
5014      while(int(leadcoef(path[1,ncols(path)]))>=comPa)
5015      {
5016         if((int(leadcoef(path[1,ncols(path)]))>comPa)&&
5017            (int(leadcoef(path[1,ncols(path)-1]))<comPa))
5018         {
5019            ERROR("L[2][comPa] not in history of L[2][o1]!");
5020         }
5021         def S=basering;
5022         if(int(leadcoef(path[1,ncols(path)]))==1)
5023         {
5024//--- that's the very first ring!!!
5025           int und_jetzt_raus;
5026         }
5027         if(defined(T)){kill T;}
5028         if(size(algext)>0)
5029         {
5030           if(defined(T0)){kill T0;}
5031           def T0=L[2][int(leadcoef(path[1,ncols(path)]))];
5032           if(defined(tstr)){kill tstr;}
5033           string tstr="ring T=(0,t),("
5034                      +varstr(L[2][int(leadcoef(path[1,ncols(path)]))])+"),("
5035                      +ordstr(L[2][int(leadcoef(path[1,ncols(path)]))])+");";
5036           execute(tstr);
5037           setring T;
5038           execute(algext);
5039           minpoly=leadcoef(p);
5040           kill tstr;
5041           def BO=imap(T0,BO);
5042           if(!defined(und_jetzt_raus))
5043           {
5044              def path=imap(T0,path);
5045              def lastMap=imap(T0,lastMap);
5046           }
5047           if(defined(idlist)){kill idlist;}
5048           list idlist=list(list(ideal(1),ideal(1)));
5049         }
5050         else
5051         {
5052           def T=L[2][int(leadcoef(path[1,ncols(path)]))];
5053           setring T;
5054           if(defined(id1)) { kill id1; }
5055           if(defined(id2)) { kill id2; }
5056           if(defined(idlist)){kill idlist;}
5057           list idlist=list(list(ideal(1),ideal(1)));
5058         }
5059         setring S;
5060         if(defined(phi)) { kill phi; }
5061         map phi=T,lastMap;
5062//--- now do the actual blowing down ...
5063         for(m=1;m<=size(idlist);m++)
5064         {
5065//--- ... for each entry of idlist separately
5066            if(defined(id1)){kill id1;}
5067            if(defined(id2)){kill id2;}
5068            ideal id1=idlist[m][1]+BO[1];
5069            ideal id2=idlist[m][2];
5070            nE=idlist[m][3];
5071            if(defined(debug_fetchInTree)>0)
5072            {
5073               "Blowing down entry",m,"of idlist:";
5074               setring S;
5075               "Abbildung:";phi;
5076               "before preimage";
5077               id1;
5078               id2;
5079            }
5080            setring T;
5081            ideal id1=preimage(S,phi,id1);
5082            ideal id2=preimage(S,phi,id2);
5083            if(defined(debug_fetchInTree)>0)
5084            {
5085               "after preimage";
5086               id1;
5087               id2;
5088            }
5089            if(size(id2)==0)
5090            {
5091//--- preimage of (principal ideal) id2 was zero, i.e.
5092//--- generator of previous id2 not in image
5093              setring S;
5094//--- it might just be one offending factor ==> factorize
5095              ideal id2factors=factorize(id2[1])[1];
5096              int zzz=size(id2factors);
5097              ideal curfactor;
5098              setring T;
5099              id2=ideal(1);
5100              ideal curfactor;
5101              for(int mm=1;mm<=zzz;mm++)
5102              {
5103//--- blow down each factor separately
5104                 setring S;
5105                 curfactor=id2factors[mm];
5106                 setring T;
5107                 curfactor=preimage(S,phi,curfactor);
5108                 if(size(curfactor)>0)
5109                 {
5110                    id2[1]=id2[1]*curfactor[1];
5111                 }
5112              }
5113              kill curfactor;
5114              setring S;
5115              kill curfactor;
5116              kill id2factors;
5117              setring T;
5118              kill mm;
5119              kill zzz;
5120              if(defined(debug_fetchInTree)>0)
5121              {
5122                 "corrected id2:";
5123                 id2;
5124              }
5125            }
5126            idlist[m]=list(id1,id2,nE);
5127            kill id1,id2;
5128            setring S;
5129         }
5130         setring T;
5131//--- after blowing down we might again be sitting inside a relevant
5132//--- exceptional divisor
5133         for(m=1;m<=size(idlist);m++)
5134         {
5135//!!! Duplicate Block!!! All changes also needed above!!!
5136//!!! no subprocedure due to large data overhead!!!
5137//--- run through all ideals to be fetched
5138            if(defined(id1)) {kill id1;}
5139            if(defined(id2)) {kill id2;}
5140            if(defined(notE)) {kill notE;}
5141            if(defined(notE)) {kill notE;}
5142            list notE;
5143            ideal id1=idlist[m][1];
5144            ideal id2=idlist[m][2];
5145            nE=idlist[m][3];
5146            for(i=branchPos-1;i<=size(BO[4]);i++)
5147            {
5148//--- run through all relevant exceptional divisors
5149               if(size(reduce(BO[4][i],std(id1)))==0)
5150               {
5151//--- V(id1) is contained in except. div. i in this chart
5152                  if(size(reduce(id1,std(BO[4][i])))!=0)
5153                  {
5154//--- V(id1) does not equal except. div. i of this chart
5155                     if(defined(Etemp)) {kill Etemp;}
5156                     ideal Etemp=BO[4][i];
5157                     if(npars(basering)>0)
5158                     {
5159//--- we are in an algebraic extension of the base field
5160                        if(defined(prtemp)){kill prtemp;}
5161                        list prtemp=minAssGTZ(BO[4][i]); // C-comp.except.div.
5162                        if(size(prtemp)>1)
5163                        {
5164//--- more than 1 component
5165                           Etemp=ideal(1);
5166                           for(j=1;j<=size(prtemp);j++)
5167                           {
5168//--- find correct component
5169                               if(size(reduce(prtemp[j],std(id1)))==0)
5170                               {
5171                                  Etemp=prtemp[j];
5172                                  break;
5173                               }
5174                           }
5175                           if(deg(std(Etemp)[1])==0)
5176                           {
5177                              ERROR("fetchInTree:something wrong in field extension");
5178                           }
5179                        }
5180                        prtemp=delete(prtemp,j); // remove this comp. from list
5181                        while(size(prtemp)>1)
5182                        {
5183//--- collect all the others into prtemp[1]
5184                           prtemp[1]=intersect(prtemp[1],prtemp[size(prtemp)]);
5185                           prtemp=delete(prtemp,size(prtemp));
5186                        }
5187                     }
5188                     if(defined(tli)) {kill tli;}
5189//--- determine tli[1] and tli[2] such that
5190//--- V(id1) \cap D(id2) = V(tli[1]) \cap D(tli[2]) \cap BO[4][i]
5191//--- inside V(BO[1]) (and if necessary inside V(BO[1]+BO[2]))
5192                     if(inJ)
5193                     {
5194                        def tli=findTrans(id1+BO[2]+BO[1],Etemp,notE,BO[2]);
5195                     }
5196                     else
5197                     {
5198                        def tli=findTrans(id1+BO[1],Etemp,notE);
5199                     }
5200                    if(npars(basering)>0)
5201                    {
5202//--- in algebraic extension: make sure we stay outside the other components
5203                      if(size(prtemp)>0)
5204                      {
5205                         for(j=1;j<=ncols(prtemp[1]);j++)
5206                         {
5207//--- find the (univariate) generator of prtemp[1] which is the remaining
5208//--- factor from the factorization over the extension field
5209                           if(size(reduce(prtemp[1][j],std(id1)))>0)
5210                           {
5211                              tli[2]=tli[2]*prtemp[1][j];
5212                           }
5213                         }
5214                      }
5215                    }
5216                  }
5217                  else
5218                  {
5219                     tli[1]=ideal(0);
5220                     tli[2]=ideal(1);
5221                  }
5222                  id1=tli[1];
5223                  id2=id2*tli[2];
5224                  notE[size(notE)+1]=BO[4][i];
5225                  for(j=1;j<=size(DivL);j++)
5226                  {
5227                     if(inIVList(intvec(o1,i),DivL[j]))
5228                     {
5229                        nE[size(nE)+1]=j;
5230                        break;
5231                     }
5232                  }
5233                  if(size(nE)<size(notE))
5234                  {
5235                     ERROR("fetchInTree: divisor not found in divL");
5236                  }
5237               }
5238               idlist[m][1]=id1;
5239               idlist[m][2]=id2;
5240               idlist[m][3]=nE;
5241            }
5242//!!! End of Duplicate Block !!!!
5243         }
5244         kill S;
5245         if(defined(und_jetzt_raus))
5246         {
5247           kill und_jetzt_raus;
5248           break;
5249         }
5250      }
5251      if(defined(debug_fetchInTree)>0)
5252      {
5253        "idlist after current blow down step:";
5254        idlist;
5255      }
5256   }
5257   if(defined(debug_fetchInTree)>0)
5258   {
5259      "Blowing down ended";
5260   }
5261//----------------------------------------------------------------------------
5262// Blow up ideal id1 from L[2][comPa] to L[2][m1]. To this end, first
5263// determine the path to follow and save it in path_togo.
5264//----------------------------------------------------------------------------
5265   if(m1==comPa)
5266   {
5267//--- no further blow ups needed
5268      if(size(algext)==0)
5269      {
5270//--- no field extension ==> we are done
5271        return(idlist[1][1]);
5272      }
5273      else
5274      {
5275//--- field extension ==> we need to encode the result
5276        list retlist;
5277        for(m=1;m<=size(idlist);m++)
5278        {
5279          retlist[m]=string(idlist[m][1]);
5280        }
5281        return(retlist);
5282      }
5283   }
5284//--- we need to blow up
5285   if(defined(path_m1)) { kill path_m1; }
5286   matrix path_m1=imap(Sm1,path);
5287   intvec path_togo;
5288   for(i=1;i<=ncols(path_m1);i++)
5289   {
5290      if(path_m1[1,i]>=comPa)
5291      {
5292        path_togo=path_togo,int(leadcoef(path_m1[1,i]));
5293      }
5294   }
5295   path_togo=path_togo[2..size(path_togo)],m1;
5296   i=1;
5297   while(i<size(path_togo))
5298   {
5299//--- we need to blow up following the path path_togo through the tree
5300      def S=basering;
5301      if(defined(T)){kill T;}
5302      if(size(algext)>0)
5303      {
5304//--- in an algebraic extension of the base field
5305         if(defined(T0)){kill T0;}
5306         def T0=L[2][path_togo[i+1]];
5307         if(defined(tstr)){kill tstr;}
5308         string tstr="ring T=(0,t),(" +varstr(T0)+"),(" +ordstr(T0)+");";
5309         execute(tstr);
5310         setring T;
5311         execute(algext);
5312         minpoly=leadcoef(p);
5313         kill tstr;
5314         def path=imap(T0,path);
5315         def BO=imap(T0,BO);
5316         def lastMap=imap(T0,lastMap);
5317         if(defined(phi)){kill phi;}
5318         map phi=S,lastMap;
5319         list idlist=phi(idlist);
5320         if(defined(debug_fetchInTree)>0)
5321         {
5322           "in blowing up (algebraic extension case):";
5323           phi;
5324           idlist;
5325         }
5326      }
5327      else
5328      {
5329         def T=L[2][path_togo[i+1]];
5330         setring T;
5331         if(defined(phi)) { kill phi; }
5332         map phi=S,lastMap;
5333         if(defined(idlist)) {kill idlist;}
5334         list idlist=phi(idlist);
5335         idlist[1][1]=radical(idlist[1][1]);
5336         idlist[1][2]=radical(idlist[1][2]);
5337         if(defined(debug_fetchInTree)>0)
5338         {
5339           "in blowing up (case without field extension):";
5340           phi;
5341           idlist;
5342         }
5343      }
5344      for(m=1;m<=size(idlist);m++)
5345      {
5346//--- get rid of new exceptional divisor
5347         idlist[m][1]=sat(idlist[m][1]+BO[1],BO[4][size(BO[4])])[1];
5348         idlist[m][2]=sat(idlist[m][2],BO[4][size(BO[4])])[1];
5349      }
5350      if(defined(debug_fetchInTree)>0)
5351      {
5352        "after saturation:";
5353        idlist;
5354      }
5355      if((size(algext)==0)&&(deg(std(idlist[1][1])[1])==0))
5356      {
5357//--- strict transform empty in this chart, it will stay empty till the end
5358         setring Sm1;
5359         return(ideal(1));
5360      }
5361      kill S;
5362      i++;
5363   }
5364   if(defined(debug_fetchInTree)>0)
5365   {
5366      "End of blowing up steps";
5367   }
5368//---------------------------------------------------------------------------
5369// prepare results for returning them
5370//---------------------------------------------------------------------------
5371   ideal E,bla;
5372   intvec kv;
5373   list retlist;
5374   for(m=1;m<=size(idlist);m++)
5375   {
5376      for(j=2;j<=size(idlist[m][3]);j++)
5377      {
5378         kv=findInIVList(1,path_togo[size(path_togo)],DivL[idlist[m][3][j]]);
5379         if(kv!=intvec(0))
5380         {
5381           E=E+BO[4][kv[2]];
5382         }
5383      }
5384      bla=quotient(idlist[m][1]+E,idlist[m][2]);
5385      retlist[m]=string(bla);
5386   }
5387   if(size(algext)==0)
5388   {
5389     return(bla);
5390   }
5391   return(retlist);
5392}
5393/////////////////////////////////////////////////////////////////////////////
5394static
5395proc findInIVList(int pos, int val, list ivl)
5396"Internal procedure - no help and no example available
5397"
5398{
5399//--- find entry with value val at position pos in list of intvecs
5400//--- and return the corresponding entry
5401   int i;
5402   for(i=1;i<=size(ivl);i++)
5403   {
5404      if(ivl[i][pos]==val)
5405      {
5406         return(ivl[i]);
5407      }
5408   }
5409   return(intvec(0));
5410}
5411/////////////////////////////////////////////////////////////////////////////
5412//static
5413proc inIVList(intvec iv, list li)
5414"Internal procedure - no help and no example available
5415"
5416{
5417//--- if intvec iv is contained in list li return 1, 0 otherwise
5418  int i;
5419  int s=size(iv);
5420  for(i=1;i<=size(li);i++)
5421  {
5422     if(typeof(li[i])!="intvec"){ERROR("Not integer vector in the list");}
5423     if(s==size(li[i]))
5424     {
5425        if(iv==li[i]){return(1);}
5426     }
5427  }
5428  return(0);
5429}
5430//////////////////////////////////////////////////////////////////////////////
5431static
5432proc Vielfachheit(ideal J,ideal I)
5433"Internal procedure - no help and no example available
5434"
5435{
5436//--- auxilliary procedure for addSelfInter
5437//--- compute multiplicity, suitable for the special situation there
5438  int d=1;
5439  int vd;
5440  int c;
5441  poly p;
5442  ideal Ip,Jp;
5443  while((d>0)||(!vd))
5444  {
5445     p=randomLast(100)[nvars(basering)];
5446     Ip=std(I+ideal(p));
5447     c++;
5448     if(c>20){ERROR("Vielfachheit: Dimension is wrong");}
5449     d=dim(Ip);
5450     vd=vdim(Ip);
5451  }
5452  Jp=std(J+ideal(p));
5453  return(vdim(Jp)/vdim(Ip));
5454}
5455/////////////////////////////////////////////////////////////////////////////
5456static
5457proc genus_E(list re, list iden0, intvec Eindex)
5458"Internal procedure - no help and no example available
5459"
5460{
5461   int i,ge,gel,num;
5462   def R=basering;
5463   ring Rhelp=0,@t,dp;
5464   def S=re[2][Eindex[1]];
5465   setring S;
5466   def Sh=S+Rhelp;
5467//----------------------------------------------------------------------------
5468//--- The Q-component X is reducible over C, decomposes into s=num components
5469//--- X_i, we assume they have n.c.
5470//---           s*g(X_i)=g(X)+s-1.
5471//----------------------------------------------------------------------------
5472   if(defined(I2)){kill I2;}
5473   ideal I2=dcE[Eindex[2]][Eindex[3]][1];
5474   num=ncols(dcE[Eindex[2]][Eindex[3]][4]);
5475   setring Sh;
5476   if(defined(I2)){kill I2;}
5477   ideal I2=imap(S,I2);
5478   I2=homog(I2,@t);
5479   ge=genus(I2);
5480   gel=(ge+(num-1))/num;
5481   if(gel*num-ge-num+1!=0){ERROR("genus_E: not divisible by num");}
5482   setring R;
5483   return(gel,num);
5484}
5485
Note: See TracBrowser for help on using the repository browser.