source: git/Singular/LIB/reszeta.lib @ 7d56875

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