source: git/Singular/LIB/reszeta.lib @ 8f296a

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