source: git/Singular/LIB/resolve.lib @ b154b3

spielwiese
Last change on this file since b154b3 was b154b3, checked in by Hans Schönemann <hannes@…>, 16 years ago
hannes: factorial -> bigint git-svn-id: file:///usr/local/Singular/svn/trunk@10596 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 134.4 KB
Line 
1///////////////////////////////////////////////////////////////////////////////
2version="$Id: resolve.lib,v 1.10 2008-02-22 14:17:21 Singular Exp $";
3category="Commutative Algebra";
4info="
5LIBRARY:  resolve.lib      Resolution of singularities (Desingularization)
6                           Algorithm of Villamayor
7AUTHORS:  A. Fruehbis-Krueger,  anne@mathematik.uni-kl.de,
8@*        G. Pfister,           pfister@mathematik.uni-kl.de
9
10MAIN PROCEDURES:
11 blowUp(J,C[,W,E]) computes the blowing up of the variety V(J) (considered
12                   as embedded in V(W)) in the (smooth) center V(C),
13 blowUp2(J,C)      computes the blowing up of the variety V(J) in the
14                   (possibly singular) center V(C)
15 Center(J[,W,E])   computes 'Villamayor'-center for blow up
16 resolve(J)        computes the desingularization of the variety V(J)
17
18PROCEDURES FOR PRETTY PRINTING OF OUTPUT:
19 showBO(BO)      prints the content of a BO in more human readable form
20 presentTree(L)  prints the final charts in more human readable form
21 showDataTypes() prints help text for output data types
22
23AUXILLARY PROCEDURES:
24 blowUpBO(BO,C)  computes the blowing up of the variety V(BO[1]) in the
25                 center V(C). BO is a list (basic object), C is an ideal
26 createBO(J,W,E) creates basic object from input data
27 CenterBO(BO)    computes the center for the next blow-up of the
28                 given basic object
29 Delta(BO)       apply the Delta-operator of [Bravo,Encinas,Villamayor]
30 DeltaList(BO)   list of results of Delta^0 to Delta^bmax
31";
32LIB "elim.lib";
33LIB "primdec.lib";
34LIB "presolve.lib";
35LIB "linalg.lib";
36LIB "sing.lib";
37///////////////////////////////////////////////////////////////////////////////
38//                      Tasks:
39//                     1) optimization of the local case
40//                     2) optimization in Coeff
41//                     3) change invariant to represent coeff=1 case
42///////////////////////////////////////////////////////////////////////////////
43
44proc showDataTypes()
45"USAGE:  showDataTypes();
46RETURN:  nothing, only pretty printing of extended version of help text
47EXAMPLE: none
48"
49{
50"                               ";
51"//////////////// Short description of data type BO ///////////////////";
52"BO[1] an ideal, say Wi, defining the ambient space of the i-th chart";
53"      of the blowing up";
54"BO[2] an ideal defining the strict transform";
55"BO[3] intvec, the first integer b such that in the original object";
56"      (Delta^b(BO[2]))==1";
57"      the subsequent integers have the same property for Coeff-Objects";
58"      of BO[2] used when determining the center";
59"BO[4] the list of exceptional divisors";
60"BO[5] an ideal defining the map K[W] ----> K[Wi]";
61"BO[6] an intvec BO[6][j]=1 indicates that <BO[4][j],BO[2]>=1, i.e. the";
62"      strict transform does not meet the j-th exceptional divisor";
63"BO[7] intvec,";
64"      the index of the first blown-up object in the resolution process";
65"      leading to this object for which the value of b was BO[3]";
66"      the subsequent ones are the indices for the Coeff-Objects";
67"      of BO[2] used when determining the center";
68"BO[i], i>7: internal data";
69"                      ";
70pause();
71"              ";
72"///////////// Short description of data in a chart ///////////////////";
73"All chart data is stored in an object of type ring, the following ";
74"variables are always present in such a ring:";
75"BO:      list of type basic object containing the variety, ambient space,";
76"         exceptional divisors and further data (see previous page)";
77"cent:    ideal, describing the upcoming center determined by the algorithm";
78"path:    module (autoconverted to matrix)";
79"         path[1][i]= (i-1)st chart in resolution history of this chart";
80"         path[2][i]= index of chart of the blow up leading to i-th chart";
81"                     in resolution history";
82"lastMap: ideal, describing the preceding blow up leading to this chart";
83"                      ";
84pause();
85"                  ";
86"///////////// Short description of type resolution data //////////////";
87"list L containing two lists:";
88"L[1]: list of rings, containing the final charts";
89"L[2]: list of rings, containing all charts created in the resolution";
90"      process";
91"The most convenient way to view these data is the procedure presentTree()";
92"from this library. Alternatively, it can be digested using tools from";
93"the libraries reszeta.lib and resgraph.lib";
94"//////////////////////////////////////////////////////////////////////";
95}
96///////////////////////////////////////////////////////////////////////////////
97proc createBO(ideal J,list #)
98"USAGE:  createBO(J[,W][,E]);
99@*       J,W = ideals
100@*       E     = list
101ASSUME:  J  = ideal containing W ( W = 0 if not specified)
102@*       E  = list of smooth hypersurfaces (e.g. exceptional divisors)
103RETURN:  list BO representing a basic object :
104         BO[1] ideal W, if W has been specified; ideal(0) otherwise
105         BO[2] ideal J
106         BO[3] intvec
107         BO[4] the list E of exceptional divisors if specified;
108               empty list otherwise
109         BO[5] an ideal defining the identity map
110         BO[6] an intvec
111         BO[7] intvec
112         BO[8] a matrix
113         entries 3,5,6,7,8 are initialized appropriately for use of CenterBO
114         and blowUpBO
115EXAMPLE: example createBO;  shows an example
116"
117{
118  ideal W;
119  list E;
120  ideal abb=maxideal(1);
121  intvec v;
122  intvec bvec;
123  intvec w=-1;
124  matrix intE;
125  if(size(#)>0)
126  {
127    if(typeof(#[1])=="ideal")
128    {
129      W=#[1];
130    }
131    if(typeof(#[1])=="list")
132    {
133      E=#[1];
134    }
135    if(size(#)>1)
136    {
137      if((typeof(#[2])=="list") && (size(E)==0))
138      {
139        E=#[2];
140      }
141      if((typeof(#[2])=="ideal") && (size(W)==0))
142      {
143        W=#[2];
144      }
145    }
146  }
147  list BO=W,J,bvec,E,abb,v,w,intE;
148  return(BO);
149}
150example
151{"EXAMPLE:";
152   echo = 2;
153   ring R=0,(x,y,z),dp;
154   ideal J=x2-y3;
155   createBO(J,ideal(z));
156}
157///////////////////////////////////////////////////////////////////////////////
158
159proc blowUp(ideal J,ideal C,list #)
160"USAGE:  blowUp(J,C[,W][,E]);
161         W,J,C = ideals,
162         E     = list
163ASSUME:  J  = ideal containing W ( W = 0 if not specified)
164@*       C  = ideal containing J
165@*       E  = list of smooth hypersurfaces (e.g. exceptional divisors)
166NOTE:    W the ideal of the ambient space, C the ideal of the center of
167         the blowup and J the ideal of the variety
168         Important difference to blowUp2:
169         - the ambient space V(W) is blown up and V(J) transformed in it
170@*         - V(C) is assumed to be non-singular
171COMPUTE: the blowing up of W in C, the exceptional locus, the strict
172         transform of J and the blowup map
173RETURN:  list, say l, of size at most size(C),
174
175         l[i] is the affine ring corresponding to the i-th chart
176         each l[i] contains the ideals
177         - aS, ideal of the blownup ambient space
178         - sT, ideal of the strict transform
179         - eD, ideal of the exceptional divisor
180         - bM, ideal corresponding to the blowup map
181
182         l[i] also contains a list BO, which can best be viewed with showBO(BO)
183         detailed information on the data type BO can be viewed via the
184         command showDataTypes();
185EXAMPLE: example blowUp;  shows an example
186"
187{
188  def S=basering;
189  ideal W;
190  list E;
191  ideal abb=maxideal(1);
192  intvec v;
193  intvec bvec;
194  intvec w=-1;
195  matrix intE;
196  if(size(#)>0)
197  {
198    if(typeof(#[1])=="ideal")
199    {
200      W=#[1];
201    }
202    if(typeof(#[1])=="list")
203    {
204      E=#[1];
205    }
206    if(size(#)>1)
207    {
208      if((typeof(#[2])=="list") && (size(E)==0))
209      {
210        E=#[2];
211      }
212      if((typeof(#[2])=="ideal") && (size(W)==0))
213      {
214        W=#[2];
215      }
216    }
217  }
218  list BO=W,J,bvec,E,abb,v,w,intE;
219  int locaT;
220  export locaT;
221  list blow=blowUpBO(BO,C,0);
222  kill locaT;
223  int i;
224  for(i=1;i<=size(blow);i++)
225  {
226     def Q=blow[i];
227     setring Q;
228     ideal aS=BO[1];
229     ideal sT=BO[2];
230     ideal eD=BO[4][size(BO[4])];
231     ideal bM=BO[5];
232     kill lastMap;
233     kill thisChart;
234     export(aS);
235     export(sT);
236     export(eD);
237     export(bM);
238     blow[i]=Q;
239     setring S;
240     kill Q;
241  }
242  return(blow);
243}
244example
245{"EXAMPLE:";
246   echo = 2;
247   ring R=0,(x,y),dp;
248   ideal J=x2-y3;
249   ideal C=x,y;
250   list blow=blowUp(J,C);
251   def Q=blow[1];
252   setring Q;
253   aS;
254   sT;
255   eD;
256   bM;
257}
258///////////////////////////////////////////////////////////////////////////////
259
260proc blowUp2(ideal J,ideal C)
261"USAGE:  blowUp2(J,C);
262         J,C = ideals,
263ASSUME:  C  = ideal containing J
264NOTE:    C the ideal of the center of the blowup and J the ideal
265         of the variety
266         Important differences to blowUp:
267         - V(J) itself is blown up, not the ambient space
268         - C is not assumed to be non-singular
269COMPUTE: the blowing up of J in C, the exceptional locus and the blow-up
270         map
271RETURN:  list, say l, of size at most size(C),
272
273         l[i] is the affine ring corresponding to the i-th chart
274         each l[i] contains the ideals
275         - Jnew, ideal of the blownup J
276         - eD, ideal of the new exceptional divisor
277         - bM, ideal corresponding to the blowup map
278
279EXAMPLE: example blowUp2;  shows an example
280"
281{
282//----------------------------------------------------------------------------
283// Initialization and basic sanity checks of the input data
284//----------------------------------------------------------------------------
285  int i,j;
286  def S=basering;
287  def laM=maxideal(1);
288//--- number of generators of C should be as small as possible
289  def mstdC=mstd(C);
290  if(ncols(mstdC[1])<ncols(mstdC[2]))
291  {
292     C=mstdC[1];
293  }
294  else
295  {
296     C=mstdC[2];
297  }
298  C=simplify(interred(C),2);
299//--- the empty set is not a good center ;-)
300  if(deg(lead(C[1]))==0)
301  {
302     ERROR("Your chosen center was the empty set. Exiting.");
303  }
304//--- V(C) should be a subset of V(J)
305  if(size(reduce(J,std(C)))>0)
306  {
307     ERROR("V(J) does not contain V(C). Exiting.");
308  }
309//---------------------------------------------------------------------------
310// To compute the blowing up, we need to consider
311//       (K[x_1,\dots,x_n]/J)[t*C[1],...,t*C[m]]
312// which we want to represent as a quotient of K[x_1,...,x_n,y_1,..,y_m]
313// by an ideal obtained by elimination of the extra variable t.
314// (in the comments n=nvars(S) and m=ncols(C))
315//---------------------------------------------------------------------------
316//--- set up rings for the elimination
317  string r1="ring R=("+charstr(basering)+"),(x(1.."+string(nvars(S));
318  r1=r1+"),y(1.."+string(ncols(C))+")),dp;";
319  string r1t="ring Rt=("+charstr(basering)+"),(x(1.."+string(nvars(S));
320  r1t=r1t+"),y(1.."+string(ncols(C))+"),t),(dp,dp(1));";
321  execute(r1);       // ring for describing the transforms
322  execute(r1t);      // like r1, but with additional variable t
323  def J=fetch(S,J);
324  def C=fetch(S,C);
325//--- we need to eliminate t from J,y(1)-t*C[1],...y(m)-t*C[m]
326  ideal elId=J;
327  for(i=1;i<=ncols(C);i++)
328  {
329     elId=elId,y(i)-t*C[i];
330  }
331  elId=eliminate(elId,t);   // ideal describing the transform of J
332  setring R;                // get rid of t
333  def elId=fetch(Rt,elId);
334  def E=fetch(S,C);         // determine exceptional divisor
335  E=E+elId;
336  def laM0=fetch(S,laM);    // the blowup map
337//-----------------------------------------------------------------------------
338// The result is now represented in an A^n \times P^{m-1}, hence
339// involving n+m variables. For further computations we would like
340// to pass to charts to keep the total number of variables as low as
341// possible
342//----------------------------------------------------------------------------
343  list resList;
344  ideal Jsub;
345  ideal Esub;
346  ideal laM;
347  ideal testId;
348  map phi;
349  list templist;
350  for(i=1;i<=nvars(R)-nvars(S);i++)
351  {
352//--- first pass elId and E on to the i-th chart
353      Jsub=std(subst(elId,y(i),1));
354      if(deg(Jsub[1])==0)
355      {
356//--- transform does not meet this chart ==> ignore it
357         i++;
358         continue;
359      }
360      Esub=std(subst(E,y(i),1));
361//--- now get rid of unnecessary variables
362//--- first by appropriate coordinate changes
363      templist=elimpart(Jsub);
364      if(size(templist[2])>0)
365      {
366         phi=R,templist[5];
367         Jsub=phi(Jsub);
368         Jsub=simplify(interred(Jsub),2);
369         Esub=phi(Esub);
370         Esub=simplify(interred(Esub),2);
371         laM=phi(laM0);
372      }
373      else
374      {
375         laM=laM0;
376      }
377//--- then by dropping non-occuring variables
378      testId=Jsub,Esub,laM;
379      templist=findvars(testId,0);
380      if(size(templist[1])<nvars(R))
381      {
382         for(j=1;j<=size(templist[4]);j++)
383         {
384            laM=subst(laM,var(templist[4][j]),0);
385         }
386         execute("ring Rnew=("+charstr(basering)+"),("+string(templist[1])+"),dp;");
387         ideal Jnew=imap(R,Jsub);
388         ideal eD=imap(R,Esub);
389         ideal bM=imap(R,laM);
390      }
391      else
392      {
393         def Rnew=basering;
394         ideal Jnew=Jsub;
395         ideal eD=Esub;
396         ideal bM=laM;
397      }
398//--- export the relevant data of this ring and add the ring to the list
399      export Jnew;
400      export eD;
401      export bM;
402      resList[size(resList)+1]=Rnew;
403      setring R;
404      kill Rnew;
405  }
406  setring S;
407  return(resList);
408}
409example
410{  "EXAMPLE:";
411   echo = 2;
412   ring r=0,(x,y,z),dp;
413   ideal I=z2-x^3*y^2;
414   ideal C=z,xy;
415   list li=blowUp2(I,C);
416   size(li);                  // number of charts
417   def S1=li[1];
418   setring S1;                // chart 1
419   basering;
420   Jnew;
421   eD;
422   bM;
423   def S2=li[2];
424   setring S2;                // chart 2
425   basering;
426   Jnew;
427   eD;
428   bM;
429}
430///////////////////////////////////////////////////////////////////////////////
431
432proc Center(ideal J,list #)
433"USAGE:  Center(J[,W][,E])
434@*       J,W = ideals
435@*       E   = list
436ASSUME:  J  = ideal containing W ( W = 0 if not specified)
437@*       E  = list of smooth hypersurfaces (e.g. exceptional divisors)
438COMPUTE: the center of the blow-up of J for the resolution algorithm
439         of [Bravo,Encinas,Villamayor]
440RETURN:  ideal, describing the center
441EXAMPLE: example Center;  shows an example
442"
443{
444  ideal W;
445  list E;
446  ideal abb=maxideal(1);
447  intvec v;
448  intvec bvec;
449  intvec w=-1;
450  matrix intE;
451  if(size(#)>0)
452  {
453    if(typeof(#[1])=="ideal")
454    {
455      W=#[1];
456    }
457    if(typeof(#[1])=="list")
458    {
459      E=#[1];
460    }
461    if(size(#)>1)
462    {
463      if((typeof(#[2])=="list") && (size(E)==0))
464      {
465        E=#[2];
466      }
467      if((typeof(#[2])=="ideal") && (size(W)==0))
468      {
469        W=#[2];
470      }
471      if(size(#)==3){bvec=#[3];}
472    }
473  }
474
475  list BO=W,J,bvec,E,abb,v,w,intE,intvec(0);
476  if(defined(invSat)){kill invSat;}
477  list invSat=ideal(0),intvec(0);
478  export(invSat);
479
480  list re=CenterBO(BO);
481  ideal cent=re[1];
482  return(cent);
483}
484example
485{  "EXAMPLE:";
486   echo = 2;
487   ring R=0,(x,y),dp;
488   ideal J=x2-y3;
489   Center(J);
490}
491///////////////////////////////////////////////////////////////////////////////
492
493proc blowUpBO(list BO, ideal C,int e)
494"USAGE:  blowUpBO (BO,C,e);
495@*       BO = basic object, a list: ideal W,
496@*                                  ideal J,
497@*                                  intvec b,
498@*                                  list Ex,
499@*                                  ideal ab,
500@*                                  intvec v,
501@*                                  intvec w,
502@*                                  matrix M
503@*       C  = ideal
504@*       e  = integer (0 usual blowing up, 1 deleting extra charts, 2 deleting
505@*            no charts )
506ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
507@*       J  = ideal containing W,
508@*       C  = ideal containing J
509COMPUTE: the blowing up of BO[1] in C, the exeptional locus, the strict
510         transform of BO[2]
511NOTE:    blowUpBO may be applied to basic objects in the sense of
512@*       [Bravo, Encinas, Villamayor] in the following referred to as BO and
513@*       to presentations in the sense of [Bierstone, Milman] in the following
514@*       referred to as BM.
515RETURN:  a list l of length at most size(C),
516         l[i] is a ring containing an object BO resp. BM:
517@*         BO[1]=BM[1] an ideal, say Wi, defining the ambient space of the
518               i-th chart of the blowing up
519@*         BO[2]=BM[2] an ideal defining the strict transform
520@*         BO[3] intvec, the first integer b such that in the original object
521               (Delta^b(BO[2]))==1
522               the subsequent integers have the same property for Coeff-Objects
523               of BO[2] used when determining the center
524@*         BM[3] intvec, BM[3][i] is the assigned multiplicity of BM[2][i]
525@*         BO[4]=BM[4] the list of exceptional divisors
526@*         BO[5]=BM[5] an ideal defining the map K[W] ----> K[Wi]
527@*         BO[6]=BM[6] an intvec BO[6][j]=1 indicates that <BO[4][j],BO[2]>=1,
528               i.e. the strict transform does not meet the j-th exceptional
529               divisor
530@*         BO[7] intvec,
531               the index of the first blown-up object in the resolution process
532               leading to this object for which the value of b was BO[3]
533               the subsequent ones are the indices for the Coeff-Objects
534               of BO[2] used when determining the center
535@*         BM[7] intvec, BM[7][i] is the index at which the (2i-1)st entry
536               of the invariant first reached its current maximal value
537@*         BO[8]=BM[8] a matrix indicating that BO[4][i] meets BO[4][j] by
538               BO[8][i,j]=1 for i < j
539@*         BO[9] empty
540@*         BM[9] the invariant
541
542EXAMPLE: example blowUpBO;  shows an example
543"
544{
545//---------------------------------------------------------------------------
546// Initialization  and sanity checks
547//---------------------------------------------------------------------------
548   def R0=basering;
549   if(!defined(locaT)){int locaT;}
550   if(locaT){poly pp=@p;}
551   intvec v;
552   int shortC=defined(shortcut);
553   int invS=defined(invSat);
554   int eq,hy;
555   int extra,noDel,keepDiv;
556   if(e==1){extra=1;}
557//---keeps all charts
558   if(e==2){noDel=1;}
559//---this is only for curves and surfaces
560//---keeps all charts with relevant informations on the exceptional divisors
561   if(e==3){keepDiv=1;}
562   if( typeof(attrib(BO[2],"isEqui"))=="int" )
563   {
564      eq=attrib(BO[2],"isEqui");
565   }
566   if( typeof(attrib(BO[2],"isHy"))=="int" )
567   {
568      hy=attrib(BO[2],"isHy");
569   }
570   string newvar;
571   int n=nvars(R0);
572   int i,j,l,m,x,jj,ll,haveCenters,co;
573//---the center should neither be the whole space nor empty
574   if((size(C)==0)||(deg(C[1])==0))
575   {
576      list result=R0;
577      return(result);
578   }
579   if(!defined(debugBlowUp))
580   {
581     int debugBlowUp=0;
582   }
583//---------------------------------------------------------------------------
584// Drop unnecessary variables
585//---------------------------------------------------------------------------
586//---step 1: substitution
587   if(!((keepDiv)||(noDel)))
588   {
589//!!! in case keepDiv and noDel:
590//!!! maybe simplify the situation by an appropriate coordinate change
591//!!! of this kind -- without dropping variables?
592      list L=elimpart(BO[1]);
593      if(size(L[2])!=0)
594      {
595         map psi=R0,L[5];
596         C=psi(C);
597         BO=psi(BO);
598      }
599
600      if(size(BO[1])==0)
601      {
602         ideal LL;
603         for(j=1;j<=size(BO[4]);j++)
604         {
605            LL=LL,BO[4][j];
606         }
607         LL=findvars(LL);
608         L=elimpart(BO[2]);
609         if((size(L[2])!=0)&&(size(std(LL+L[2]))==size(L[2])+size(LL)))
610         {
611            map chi=R0,L[5];
612            C=chi(C);
613            BO=chi(BO);
614         }
615      }
616//---step 2: dropping non-occurring variables
617      int s=size(C);
618      ideal K=BO[1],BO[2],C;
619      for(j=1;j<=size(BO[4]);j++)
620      {
621        K=K,BO[4][j];
622      }
623      list N=findvars(K,0);
624      if(size(N[1])<n)
625      {
626         newvar=string(N[1]);
627         v=N[4];
628         for(j=1;j<=size(v);j++){BO[5]=subst(BO[5],var(v[j]),0);}
629         execute("ring R1=("+charstr(R0)+"),("+newvar+"),dp;");
630         list BO=imap(R0,BO);
631         ideal C=imap(R0,C);
632         n=nvars(R1);
633      }
634      else
635      {
636         def R1=basering;
637      }
638   }
639   else
640   {
641     int s=size(C);
642     def R1=basering;
643   }
644   if(debugBlowUp)
645   {
646     "---> In BlowUp: After dropping unnecessary variables";
647     "BO:";
648     BO;
649     "C:";
650     C;
651   }
652//---------------------------------------------------------------------------
653// Do the actual blow-up
654//---------------------------------------------------------------------------
655//--- control the names of the variables
656   execute("ring R=("+charstr(R0)+"),(x(1..n)),dp;");
657   list BO=fetch(R1,BO);
658   ideal C=fetch(R1,C);
659   list Cmstd=mstd(C);
660   C=Cmstd[2];
661   if(size(Cmstd[1])<=size(Cmstd[2]))
662   {
663      C=Cmstd[1];
664   }
665   else
666   {
667      C=interred(C);
668   }
669   list result;
670//--- the blow-up process
671   ideal W  =BO[1];
672   ideal J  =BO[2];
673   intvec bvec  =BO[3];
674   list Ex  =BO[4];
675   ideal abb=BO[5];
676   intvec wvec=BO[7];
677   ideal laM=maxideal(1);
678   if((typeof(BO[9])=="intmat")||(typeof(BO[9])=="intvec"))
679   {
680      def @invmat=BO[9];
681   }
682   if(size(BO)>9)
683   {
684//--- check whether a previous center had been split into connected components
685      if(size(BO[10])>0)
686      {
687         list knownCenters=BO[10];
688         haveCenters=1;
689       }
690   }
691
692   matrix intE=BO[8];
693   Ex[size(Ex)+1]=var(1);
694         //to have the list depending on R in case BO[4] is empty
695
696   execute("ring S=("+charstr(R)+"),("+varstr(R)+",y(0..s-1)),dp;");
697   list resu;
698   list B;
699   execute("ring T=("+charstr(R)+"),("+varstr(R)+",y(0..s-1),t),dp;");
700   ideal C=imap(R,C);
701   ideal W=imap(R,W);
702   execute("map phi=S,"+varstr(R)+",t*C;")
703   setring S;
704
705//--- the ideal describing the blow-up map
706   ideal abb=imap(R,abb);
707   ideal laM0=imap(R,laM);
708//--- the ideal of the blowing up of the ambient space
709   ideal W=preimage(T,phi,W);
710//--- the ideal of the exceptional locus
711   ideal E=imap(R,C);
712
713   list E1=imap(R,Ex);
714   E1[size(E1)]=E;
715   ideal J=imap(R,J)+W;
716
717   if(haveCenters){list kN=imap(R,knownCenters);}
718
719//---  the strict transform of the exceptional divisors
720   for(j=1;j<size(E1);j++){E1[j]=sat(E1[j]+W,E)[1];}
721//---  the intersection matrix of the exceptional divisors
722   matrix intEold=imap(R,intE);
723   matrix intE[size(E1)][size(E1)];
724   ideal U,Jsub,sLstd;
725
726   for(j=1;j<size(E1);j++)
727   {
728       for(l=j+1;l<=size(E1);l++)
729       {
730          if(deg(E1[j][1])==0)
731          {
732             if(l<size(E1)){intE[j,l]=intEold[j,l];}
733             else             {intE[j,l]=0;}
734          }
735          else
736          {
737             if(deg(E1[l][1])==0)
738             {
739                if(l<size(E1)){intE[j,l]=intEold[j,l];}
740             }
741             else
742             {
743                U= std(E1[l]+E1[j]);
744                if(dim(U)>0){intE[j,l]=1;}
745                else        {intE[j,l]=0;}
746             }
747          }
748       }
749   }
750   if(debugBlowUp)
751   {
752     "----> In BlowUp: After Blowing-up, before Clean-Up";
753     "W:";
754     W;
755     "J:";
756     J;
757   }
758//----------------------------------------------------------------------------
759// generating and cleaning up the different charts
760//----------------------------------------------------------------------------
761   list M;
762   map psi;
763   list E2;
764   ideal K,JJ,laM,LL,MM;
765   n=nvars(S);
766   list N;
767   list Bstd;
768   intvec delCharts,extraCharts;
769   delCharts[s]=0;
770   extraCharts[s]=0;
771   ideal MA=y(0..s-1);
772   list ZRes,ZlaM,ZsLstd;
773   for(i=0;i<=s-1;i++)
774   {
775     if(haveCenters)
776     {
777        B[10]=kN;
778        for(j=1;j<=size(kN);j++)
779        {
780           B[10][j][1]=subst(B[10][j][1],y(i),1);
781        }
782     }
783     B[8]=intE;
784     B[1]=std(subst(W,y(i),1));
785     if(deg(B[1][1])==0)
786     {
787//--- subsets of the empty set are not really interesting!
788       delCharts[i+1]=1;
789       ZRes[i+1]=B;
790       ZlaM[i+1]=laM;
791       i++;
792       continue;
793     }
794     Jsub=subst(J,y(i),1);
795     attrib(Jsub,"isEqui",eq);
796     attrib(Jsub,"isHy",hy);
797     B[2]=Jsub;
798     B[3]=bvec;
799     for(j=1;j<size(E1);j++){E2[j]=subst(E1[j],y(i),1);}
800     E2[size(E1)]=E+B[1];
801     B[4]=E2;
802     M=elimpart(B[1]);
803     B[5]=abb;
804     laM=laM0;
805     psi=S,maxideal(1);
806     if(size(M[2])!=0)
807     {
808        psi=S,M[5];
809        B=psi(B);
810        laM=psi(laM);
811     }
812     Jsub=B[2];
813     B[2]=sat(Jsub,std(psi(E)))[1];
814     if(!defined(MAtmp)){ideal MAtmp=MA;}
815     MAtmp[i+1]=0;
816     JJ=std(B[2]+MAtmp);
817     if(deg(JJ[1])==0)
818     {
819        delCharts[i+1]=1;
820//--- the i-th chart will be marked for deleting because all informations
821//--- are already contained in the union of the remaining charts
822     }
823     else
824     {
825        if((eq)&&(dim(JJ)<dim(std(B[2]))))
826        {
827           extraCharts[i+1]=1;
828//---  compute the singular locus
829           if((B[3][1]<=1)&&(hy))
830//--- B[2] is a smooth hypersurface
831           {
832              sLstd=ideal(1);
833           }
834           else
835           {
836              Bstd=mstd(B[2]);
837              if(n-dim(Bstd[1])>4)
838              {
839//--- in this case the singular locus is too complicated
840                 sLstd=ideal(0);
841              }
842              JJ=Bstd[2];
843              attrib(JJ,"isEqui",eq);
844              B[2]=JJ;
845              sLstd=slocusE(B[2]);
846           }
847           m=0;
848           if(deg(std(sLstd+MAtmp)[1])==0)
849           {
850//--- the singular locus of B[2] is in the union of the remaining charts
851              m=1;
852              for(l=1;l<=size(B[4]);l++)
853              {
854                 if(deg(std(B[2]+B[4][l]+MAtmp)[1])!=0)
855                 {
856//--- the exceptional divisor meets B[2] at the locus of MAtmp
857//--- we continue only if the option extra=1 and we have transversal
858//--- intersection
859                    m=0;
860                    break;
861                  }
862              }
863           }
864           if(m)
865           {
866//--- the i-th chart will be marked for deleting because all informations
867//--- are already contained in the union of the remaining charts
868              delCharts[i+1]=1;
869           }
870        }
871     }
872     if(delCharts[i+1]==0)
873     {
874        MAtmp[i+1]=MA[i+1];
875        ZsLstd[i+1]=sLstd;
876     }
877     ZRes[i+1]=B;
878     ZlaM[i+1]=laM;
879   }
880//---------------------------------------------------------------------------
881// extra = ignore uninteresting charts even if there is a normal
882//         crosssing intersection in it
883//---------------------------------------------------------------------------
884   if(extra)
885   {
886      for(i=0;i<=s-1;i++)
887      {
888         if((delCharts[i+1]==0)&&(extraCharts[i+1]))
889         {
890           MAtmp[i+1]=0;
891           B=ZRes[i+1];
892           sLstd=ZsLstd[i+1];
893           m=0;
894           if(deg(std(sLstd+MAtmp)[1])==0)
895           {
896//--- the singular locus of B[2] is in the union of the remaining charts
897              m=1;
898              for(l=1;l<=size(B[4]);l++)
899              {
900                 if(deg(std(B[2]+B[4][l]+MAtmp)[1])!=0)
901                 {
902//--- the exceptional divisor meets B[2] at the locus of MAtmp
903//--- we continue only if the option extra=1 and we have transversal
904//--- intersection
905                    m=2;
906                    if(!transversalTB(B[2],list(B[4][l]),MAtmp))
907                    {
908                       m=0;break;
909                    }
910                  }
911              }
912           }
913           if(m)
914           {
915              if(m==1)
916              {
917//--- the i-th chart will be marked for deleting because all informations
918//--- are already contained in the union of the remaining charts
919                 delCharts[i+1]=1;
920              }
921              else
922              {
923//--- the option extra=1 and we have transversal intersection
924//--- we delete the chart in case of normal crossings
925                 if(normalCrossB(B[2],B[4],MAtmp))
926                 {
927//--- in case of the option extra
928//--- the i-th chart will be marked for deleting because all informations
929//--- are already contained in the union of the remaining charts
930
931                   delCharts[i+1]=1;
932                 }
933              }
934           }
935           if(delCharts[i+1]==0)
936           {
937              MAtmp[i+1]=MA[i+1];
938           }
939         }
940      }
941      for(i=0;i<=s-1;i++)
942      {
943         if(!delCharts[i+1]){break;}
944      }
945      if(i==s){delCharts[s]=0;}
946   }
947   for(i=0;i<=s-1;i++)
948   {
949     B=ZRes[i+1];
950     laM=ZlaM[i+1];
951     if(noDel){delCharts[i+1]=0;}
952//---keeps chart if the exceptional divisor is not in any other chart
953     if((delCharts[i+1])&&(keepDiv))
954     {
955         for(j=1;j<=size(B[4]);j++)
956         {
957            if(deg(std(B[4][j])[1])>0)
958            {
959               x=0;
960               for(l=0;l<=s-1;l++)
961               {
962                  if((l!=i)&&(!delCharts[l+1])&&(deg(std(ZRes[l+1][4][j])[1])>0))
963                  {
964                     x=1;
965                     break;
966                  }
967               }
968               if(!x)
969               {
970                  delCharts[i+1]=0;
971//!!!evtl. diese Karten markieren und nicht weiter aufblasen???
972                  break;
973               }
974            }
975         }
976     }
977//---keeps charts if the intersection of 2 divisors is not in any other chart
978     if((delCharts[i+1])&&(keepDiv))
979     {
980         for(j=1;j<=size(B[4])-1;j++)
981         {
982            for(l=j+1;l<=size(B[4]);l++)
983            {
984               if(deg(std(B[4][j]+B[4][l])[1])>0)
985               {
986                  x=0;
987                  for(ll=0;ll<=s-1;ll++)
988                  {
989                     if((ll!=i)&&(!delCharts[ll+1]))
990                     {
991                        if(deg(std(ZRes[ll+1][4][j]+ZRes[ll+1][4][l])[1])>0)
992                        {
993                           x=1;
994                           break;
995                        }
996                     }
997                  }
998                  if(!x)
999                  {
1000                     delCharts[i+1]=0;
1001                     break;
1002                  }
1003               }
1004            }
1005            if(!delCharts[i+1]){break;}
1006         }
1007     }
1008//---keeps charts if the intersection of 3 divisors is not in any other chart
1009     if((delCharts[i+1])&&(keepDiv))
1010     {
1011         for(j=1;j<=size(B[4])-2;j++)
1012         {
1013            for(l=j+1;l<=size(B[4])-1;l++)
1014            {
1015               for(ll=l+1;ll<=size(B[4]);ll++)
1016               {
1017                  if(deg(std(B[4][j]+B[4][l]+B[4][ll])[1])>0)
1018                  {
1019                     x=0;
1020                     for(jj=0;jj<=s-1;jj++)
1021                     {
1022                        if((jj!=i)&&(!delCharts[jj+1]))
1023                        {
1024                           if(deg(std(ZRes[jj+1][4][j]
1025                              +ZRes[jj+1][4][l]+ZRes[jj+1][4][ll])[1])>0)
1026                           {
1027                              x=1;
1028                              break;
1029                           }
1030                        }
1031                     }
1032                     if(!x)
1033                     {
1034                       delCharts[i+1]=0;
1035                       break;
1036                     }
1037                  }
1038               }
1039               if(!delCharts[i+1]){break;}
1040            }
1041            if(!delCharts[i+1]){break;}
1042        }
1043     }
1044     if(delCharts[i+1]==0)
1045     {
1046//--- try to decrease the number of variables by substitution
1047        if((!keepDiv)&&(!noDel))
1048        {
1049           list WW=elimpart(B[1]);
1050           map phiW=basering,WW[5];
1051           B=phiW(B);
1052           laM=phiW(laM);
1053           kill WW;
1054           kill phiW;
1055           if(size(B[1])==0)
1056           {
1057              LL=0;
1058              for(j=1;j<=size(B[4]);j++)
1059              {
1060                 MM=std(B[4][j]);
1061                 if(deg(MM[1])>0){LL=LL,MM;}
1062              }
1063              LL=findvars(LL);
1064              M=elimpart(B[2]);
1065              if((size(M[2])!=0)&&(size(std(LL+M[2]))==size(M[2])+size(LL)))
1066              {
1067                psi=S,M[5];
1068                B=psi(B);
1069                laM=psi(laM);
1070              }
1071           }
1072         }
1073//---- interreduce B[1],B[2] and all B[4][j]
1074        B[1]=interred(B[1]);
1075        B[2]=interred(B[2]);
1076        E2=B[4];
1077        for(j=1;j<=size(E2);j++){E2[j]=interred(E2[j]);}
1078        B[4]=E2;
1079        v=0;v[size(E2)]=0;
1080//--- mark those j for which B[4] does not meet B[2]
1081        for(j=1;j<=size(E2);j++)
1082        {
1083            K=E2[j],B[2];
1084            K=std(K);
1085            if(deg(K[1])==0)
1086            {
1087              v[j]=1;
1088            }
1089        }
1090        B[6]=v;
1091        B[7]=wvec;
1092//--- throw away variables which do not occur
1093        K=B[1],B[2],B[5];          //Aenderung!!!
1094        for(j=1;j<=size(B[4]);j++){K=K,B[4][j];}
1095        N=findvars(K,0);
1096        if(size(N[1])<n)
1097        {
1098           newvar=string(N[1]);
1099           v=N[4];
1100           for(j=1;j<=size(v);j++)
1101           {
1102              B[5]=subst(B[5],var(v[j]),0);
1103              laM=subst(laM,var(v[j]),0);
1104           }
1105           execute("ring R2=("+charstr(S)+"),("+newvar+"),dp;");
1106           list BO=imap(S,B);
1107           ideal laM=imap(S,laM);
1108        }
1109        else
1110        {
1111           def R2=basering;
1112           list BO=B;
1113        }
1114        ideal JJ=BO[2];
1115        attrib(JJ,"isEqui",eq);
1116        attrib(JJ,"isHy",hy);
1117        BO[2]=JJ;
1118//--- strict transforms of the known centers
1119        if(haveCenters)
1120        {
1121           ideal tt;
1122           list tList;
1123           for(j=1;j<=size(BO[10]);j++)
1124           {
1125              tt=std(BO[10][j][1]);
1126              if(deg(tt[1])>0)
1127              {
1128                tt=sat(tt,BO[4][size(BO[4])])[1];
1129              }
1130              if((deg(tt[1])>0)&&(deg(std(tt+BO[2]+BO[1])[1])>0))
1131              {
1132                 tList[size(tList)+1]=
1133                            list(tt,BO[10][j][2],BO[10][j][3],BO[10][j][4]);
1134              }
1135           }
1136           BO[10]=tList;
1137           kill tList;
1138        }
1139//--- marking  variables which do not occur in BO[1] and BO[2]
1140//--- and occur in exactly one BO[4][j], which is the hyperplane given by
1141//--- this variable
1142//!!!! not necessarily in exactly one BO[4][j]
1143        list N=findvars(BO[1]+BO[2],0);
1144        if(size(N[1])<nvars(basering))
1145        {
1146           v=N[4];
1147           if(defined(H)){kill H;}
1148           if(defined(EE)){kill EE;}
1149           if(defined(vv)){kill vv;}
1150           list EE;
1151           intvec vv;
1152           ideal H=maxideal(1);
1153           for(j=1;j<=size(v);j++)
1154           {
1155             H[v[j]]=0;
1156           }
1157           H=std(H);
1158           for(l=1;l<=size(BO[4]);l++)
1159           {
1160              if(BO[6][l]==1){l++;continue;}
1161              if(size(ideal(reduce(BO[4][l],H)-BO[4][l]))==0)
1162              {
1163//!!! need further cleanup:
1164//!!! this part of the code is no longer used since it did not glue properly
1165//                 BO[6][l]=2;
1166                 EE[size(EE)+1]=BO[4][l];
1167                 vv[size(vv)+1]=l;
1168              }
1169           }
1170           if((size(vv)>dim(std(BO[2])))&&(deg(BO[2][1])>0))
1171           {
1172              list BOtemp3=BO;
1173              BOtemp3[4]=EE;
1174              intvec ivtemp3;
1175              ivtemp3[size(BOtemp3[4])]=0;
1176              BOtemp3[6]=ivtemp3;
1177              BOtemp3[7][1]=-1;
1178              list iEtemp3=inters_E(BOtemp3);
1179              if(iEtemp3[2]>=dim(std(BOtemp3[2])))
1180              {
1181                 for(l=2;l<=size(vv);l++)
1182                 {
1183                    BO[6][vv[l]]=0;
1184                 }
1185              }
1186              kill BOtemp3,ivtemp3,iEtemp3;
1187           }
1188        }
1189        list thisChart=ideal(0),i;
1190        export thisChart;
1191
1192//----------------------------------------------------------------------------
1193// export the basic object and append the ring to the list of rings
1194//----------------------------------------------------------------------------
1195        if(debugBlowUp)
1196        {
1197           "----> In BlowUp: Adding a single chart";
1198           "BO:";
1199           BO;
1200        }
1201        if(locaT)
1202        {
1203           map locaPhi=R0,laM;
1204           poly @p=locaPhi(pp);
1205           export(@p);
1206        }
1207        ideal lastMap=laM;
1208        export lastMap;
1209        if(invS){list invSat=imap(R0,invSat);export invSat;}
1210        if(defined(@invmat)){BO[9]=@invmat;}
1211        if(shortC){list shortcut=imap(R0,shortcut);export(shortcut);}
1212        export BO;
1213        result[size(result)+1]=R2;
1214        setring S;
1215        kill R2;
1216     }
1217   }
1218   setring R0;
1219   return(result);
1220}
1221example
1222{"EXAMPLE:";
1223   echo = 2;
1224   ring R=0,(x,y),dp;
1225
1226   ideal W;
1227   ideal J=x2-y3;
1228   intvec b=1;
1229   list E;
1230   ideal abb=maxideal(1);
1231   intvec v;
1232   intvec w=-1;
1233   matrix M;
1234   intvec ma;
1235   list BO=W,J,b,E,abb,v,w,M,ma;
1236
1237   ideal C=CenterBO(BO)[1];
1238
1239   list blow=blowUpBO(BO,C,0);
1240   def Q=blow[1];
1241   setring Q;
1242   BO;
1243}
1244//////////////////////////////////////////////////////////////////////////////
1245static
1246proc slocusE(ideal i)
1247"Internal procedure - no help and no example available
1248"
1249{
1250//--- do slocus in equidimensional case directly -- speed up
1251  if(size(i)==0){return(ideal(1));}
1252  if( typeof(attrib(i,"isEqui"))=="int" )
1253  {
1254     if(attrib(i,"isEqui")==1)
1255     {
1256        ideal j=std(i);
1257        if(deg(j[1])==0){return(j);}
1258        int cod  = nvars(basering)-dim(j);
1259        i        = i+minor(jacob(i),cod);
1260        return(i);
1261     }
1262  }
1263  return(slocus(i));
1264}
1265///////////////////////////////////////////////////////////////////////////////
1266static
1267proc inters_E(list BO)
1268"USAGE:  inters_E(BO);
1269@*       BO = basic object, a list: ideal W,
1270@*                                  ideal J,
1271@*                                  intvec b,
1272@*                                  list Ex,
1273@*                                  ideal ab,
1274@*                                  intvec v,
1275@*                                  intvec w,
1276@*                                  matrix M
1277ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
1278@*       J  = ideal containing W,
1279@*       BO in the setting of case 2 of [Bravo,Encinas,Villamayor]
1280@*             BO[4]=E, BO[4][1..count]=E^-
1281@*             BO[7][1]=count
1282COMPUTE: (W,(P,1),E^+) in the notation of [Bravo,Encinas,Villamayor]
1283RETURN:  a list l ,
1284         l[1]: P = product of ideals I(H_i1)+..+I(H_in) over all
1285                   n-tuples of indices i1..in from 1..count
1286         l[2]: n = maximal number of H_i from E^- meeting J simultaneously
1287         l[3]: maximal number of H_i from E meeting J simultaneously
1288EXAMPLE: internal procedure - no example available
1289"
1290{
1291//---------------------------------------------------------------------
1292// Initialization
1293//---------------------------------------------------------------------
1294  int kk,jj,ii,updated,n,count2,kkdiff;
1295  def rb=basering;
1296  def W=BO[1];
1297  ideal J=BO[1],BO[2];
1298  int nonnormal;
1299  int maxkk=dim(std(J));
1300  int dimJ=maxkk;
1301  ideal test2;
1302  list merklist1,merklist2;
1303  if(size(BO[4])==0)
1304  {
1305    list retlist=BO[2],n;
1306    return(retlist);
1307  }
1308  def E=BO[4];
1309  intvec stoplist=BO[6];
1310//--- fill in all known information about exceptional divisors not meeting
1311//--- current chart
1312  for(ii=1;ii<=size(E);ii++)
1313  {
1314    if(deg(std(E[ii])[1])==0)
1315    {
1316      stoplist[ii]=1;
1317    }
1318  }
1319
1320  int count=BO[7][1];
1321  if(!defined(debug_Inters_E))
1322  {
1323    int debug_Inters_E=0;
1324  }
1325//---------------------------------------------------------------------
1326// we only want to look at E^-, not at all of E
1327//---------------------------------------------------------------------
1328  if (count>-1)
1329  {
1330    if (count>0)
1331    {
1332      list E_new=E[1..count];
1333      count2=size(E);
1334    }
1335    else
1336    {
1337      list E_new;
1338      count2=size(E);
1339    }
1340  }
1341  else
1342  {
1343    list E_new=E;
1344    count=size(E_new);
1345    count2=count;
1346  }
1347//---------------------------------------------------------------------
1348// combinatorics is expensive in an interpreted language,
1349// we leave it to the kernel by translating it into monomial
1350// ideals in a new ring with variables t(i)
1351//---------------------------------------------------------------------
1352  string rstr="ring rcomb=0,(t(1.." + string(size(E)) + ")),dp;";
1353  execute(rstr);
1354  ideal potid,potid2;
1355  list monlist,comblist,merkmon;
1356  for(kk=1;kk<=count;kk++)
1357  {
1358    if(stoplist[kk]==0)
1359    {
1360//**************************************************************************/
1361// it does not make sense to intersect twice by the same E_i
1362// ===> reduce by t(i)^2
1363//**************************************************************************/
1364      potid=potid,t(kk)^2;
1365    }
1366    else
1367    {
1368//**************************************************************************/
1369// it does not make sense to consider E_i with v[i]==1 ===> reduce by t(i)
1370//**************************************************************************/
1371      potid=potid,t(kk);
1372//**************************************************************************/
1373// if stoplist[kk]==2 then J and all E_i automatically intersect E_kk
1374// hence we need not test it, but we have to lower maxkk by one
1375//**************************************************************************/
1376      if(stoplist[kk]==2)
1377      {
1378        maxkk=maxkk-1;
1379        kkdiff++;             // count these for dimension check later on
1380
1381      }
1382    }
1383  }
1384
1385  potid2=std(potid);
1386  if(count2>count)
1387  {
1388    potid=potid,t((count+1)..count2);
1389    for(kk=max(1,count);kk<=count2;kk++)
1390    {
1391      potid2=potid2,t(kk)^2;
1392    }
1393  }
1394  potid=std(potid);
1395  potid2=std(potid2);
1396  for(kk=1;(((kk<=count)||(kk<=maxkk+1))&&(kk<=count2));kk++)
1397  {
1398//-------------------------------------------------------------------------
1399// monlist[kk]=lists of kk entries of E_new, not containing an E_i twice,
1400// not containing an E_i where v[i]==1
1401//-------------------------------------------------------------------------
1402    monlist[kk]=redMax(kk,potid);
1403//*************************************************************************/
1404// in the case of n<=maxkk we also need to know whether n would still be
1405// below this bound if we considered all of E instead of E_new
1406// ===> merkmon contains previously ignored tuples E_i1,..,E_im
1407//*************************************************************************/
1408    if(kk<=maxkk+1)
1409    {
1410      merkmon[kk]=redMax(kk,potid2);
1411      merkmon[kk]=simplify(reduce(merkmon[kk],std(monlist[kk])),2);
1412    }
1413  }
1414  if(debug_Inters_E)
1415  {
1416    "----> In Inters_E: the tuples";
1417    "tuples of E^-:";
1418    monlist;
1419    "the remaining tuples:";
1420    merkmon;
1421  }
1422//-------------------------------------------------------------------------
1423// check whether there is a kk-tuple of E_i intersecting J,
1424// kk running from 1 to count
1425//-------------------------------------------------------------------------
1426  for(kk=1;kk<=count;kk++)
1427  {
1428    if(size(monlist[kk]==0)) break;
1429    kill comblist;
1430    list comblist;
1431//--- transscribe the tuples from monomial notation to intvec notation
1432    for(jj=1;jj<=ncols(monlist[kk]);jj++)
1433    {
1434      comblist[jj]=leadexp(monlist[kk][jj]);
1435    }
1436    setring rb;
1437    updated=0;
1438//------------------------------------------------------------------------
1439// Do the intersections
1440//------------------------------------------------------------------------
1441    for(jj=1;jj<=size(comblist);jj++)
1442    {
1443//--- jj-th tuple from list of tuples of kk E_i
1444      test2=J;
1445      for(ii=1;ii<=count;ii++)
1446      {
1447        if(comblist[jj][ii]==1)
1448        {
1449          test2=test2,E_new[ii];
1450        }
1451      }
1452      test2=std(test2);
1453//--- check whether this intersection is non-empty and store it accordingly
1454      if(deg(test2[1])!=0)
1455      {
1456//--- it is non-empty
1457        if(updated!=0)
1458        {
1459          merklist1[size(merklist1)+1]=comblist[jj];
1460        }
1461        else
1462        {
1463          kill merklist1;
1464          list merklist1;
1465          merklist1[1]=comblist[jj];
1466          updated=1;
1467          n=kk;
1468        }
1469        if(dim(test2)!=maxkk-kk+kkdiff)
1470        {
1471          nonnormal=1;
1472        }
1473      }
1474      else
1475      {
1476//--- it is empty
1477        merklist2[size(merklist2)+1]=jj;
1478      }
1479    }
1480    setring rcomb;
1481    ideal redid;
1482//---------------------------------------------------------------------
1483// update monlist and merkmon by the knowledge what intersections are
1484// empty in the kk-th step
1485//---------------------------------------------------------------------
1486    for(jj=1;jj<=size(merklist2);jj++)
1487    {
1488      redid=redid,monlist[kk][merklist2[jj]];
1489    }
1490    for(jj=kk+1;jj<=count;jj++)
1491    {
1492      monlist[jj]=simplify(reduce(monlist[jj],std(redid)),2);
1493      if(jj<=maxkk+1)
1494      {
1495        merkmon[jj]=simplify(reduce(merkmon[jj],std(redid)),2);
1496      }
1497    }
1498    kill redid;
1499    kill merklist2;
1500    list merklist2;
1501  }
1502  if(debug_Inters_E)
1503  {
1504    "----> In Inters_E: intersections found:";
1505    merklist1;
1506  }
1507//---------------------------------------------------------------------
1508// form the union of the intersections of the appropriate E_i
1509//---------------------------------------------------------------------
1510  setring rb;
1511  ideal center,dummy;
1512  list centlist;
1513  for(kk=1;kk<=size(merklist1);kk++)
1514  {
1515    for(jj=1;jj<=size(merklist1[kk]);jj++)
1516    {
1517      if(merklist1[kk][jj]==1)
1518      {
1519        dummy=dummy,E_new[jj];
1520      }
1521    }
1522    if(size(center)==0)
1523    {
1524      center=dummy;
1525      centlist[1]=dummy;
1526    }
1527    else
1528    {
1529      center=intersect(center,dummy);
1530      centlist[size(centlist)+1]=dummy;
1531    }
1532    dummy=0;
1533  }
1534  if(debug_Inters_E)
1535  {
1536    "----> In Inters_E: intersection of E_i";
1537    "maximal number of E_i encountered in:";
1538    center;
1539    "the components of this locus:";
1540    centlist;
1541    "maximal number of E_i from E^- intersecting simultaneously:",n;
1542    if(nonnormal)
1543    {
1544      "flag nonnormal is set";
1545    }
1546  }
1547  list retlist=center,n;
1548//-------------------------------------------------------------------------
1549// If n<=maxkk, then test if this is the case for all of E not just E_new
1550// using the pairs indicated by merkmon
1551//-------------------------------------------------------------------------
1552  int ntotal=n;
1553  if((n<=maxkk)&&(n<count2)&&(!nonnormal))
1554  {
1555//--- check kk-tuples
1556    for(kk=n+1;kk<=maxkk+1;kk++)
1557    {
1558      setring rcomb;
1559//--- check if there are combinations to be checked
1560      if(kk>size(merkmon))
1561      {
1562        setring rb;
1563        break;
1564      }
1565      if(size(merkmon[kk])!=0)
1566      {
1567        kill comblist;
1568        list comblist;
1569//--- transscribe tuples from  monomial notation to intvec notation
1570        for(jj=1;jj<=size(merkmon[kk]);jj++)
1571        {
1572          comblist[jj]=leadexp(merkmon[kk][jj]);
1573        }
1574        setring rb;
1575//--- check jj-th tuple from the list of kk-tuples
1576        for(jj=1;jj<=size(comblist);jj++)
1577        {
1578          test2=J;
1579          for(ii=1;ii<=nvars(rcomb);ii++)
1580          {
1581            if(comblist[jj][ii]==1)
1582            {
1583              test2=test2,E[ii];
1584            }
1585          }
1586          test2=std(test2);
1587//--- as soon as we found one we can proceed to the subsequent kk
1588          if(deg(test2[1])!=0)
1589          {
1590            ntotal=kk;
1591            if(dim(test2)-kkdiff!=maxkk-kk)
1592            {
1593              nonnormal=2;
1594              break;
1595            }
1596          }
1597        }
1598//--- if we already know that too many E_i intersect simultaneously,
1599//--- we need not proceed any further
1600        if(nonnormal)
1601        {
1602          break;
1603        }
1604      }
1605      else
1606      {
1607        setring rb;
1608        break;
1609      }
1610    }
1611  }
1612//-------------------------------------------------------------------------
1613// update the result accordingly and return it
1614//-------------------------------------------------------------------------
1615  if(maxkk<dimJ)
1616  {
1617    n=n+dimJ-maxkk;
1618    ntotal=ntotal+dimJ-maxkk;
1619  }
1620  retlist[2]=n;
1621  retlist[3]=ntotal;
1622  if(n<=dimJ)
1623  {
1624    retlist[4]=centlist;
1625    retlist[5]=merklist1;
1626    if(nonnormal)
1627    {
1628      retlist[6]=nonnormal;
1629    }
1630  }
1631  return(retlist);
1632}
1633///////////////////////////////////////////////////////////////////////////
1634
1635proc Delta(list BO)
1636"USAGE:  Delta (BO);
1637@*       BO = basic object, a list: ideal W,
1638@*                                  ideal J,
1639@*                                  intvec b,
1640@*                                  list Ex,
1641@*                                  ideal ab,
1642@*                                  intvec v,
1643@*                                  intvec w,
1644@*                                  matrix M
1645ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
1646@*       J  = ideal containing W
1647COMPUTE: Delta-operator applied to J in the notation of
1648         [Bravo,Encinas,Villamayor]
1649RETURN:  ideal
1650EXAMPLE: example Delta;  shows an example
1651"
1652{
1653//---------------------------------------------------------------------------
1654// Initialization  and sanity checks
1655//---------------------------------------------------------------------------
1656   ideal W=BO[1];
1657   ideal J=BO[2];
1658   ideal C=simplify(reduce(J,std(W)),2);
1659   list LC;
1660   int n=nvars(basering);
1661//---------------------------------------------------------------------------
1662// Simple case: W is the empty set
1663//---------------------------------------------------------------------------
1664   if(size(W)==0)
1665   {
1666      C=C,jacob(J);
1667      C=std(C);
1668      return(C);
1669   }
1670//---------------------------------------------------------------------------
1671// General case: W is non-empty
1672// Step 1: Find a minor of the Jacobian of W which is not identically zero
1673//         and look at the complement of the zero-set given by this minor;
1674//         this leads to the system of local parameters
1675// Step 2: Form the derivatives w.r.t. this system of parameters
1676//---------------------------------------------------------------------------
1677//--- Step 1
1678   list re=findMinor(W);
1679   list L;
1680   int ii,i,j,l,k;
1681   J=C;
1682   ideal D=ideal(1);
1683   intvec v,w;
1684   ideal V;
1685   poly m;
1686
1687   for(ii=1;ii<=size(re);ii++)
1688   {
1689      C=J;
1690      L=re[ii];
1691      matrix A=L[1];  //(1/m)*A is the inverse matrix of the Jacobian of W
1692                      //corresponding to m
1693      m=L[2];  //a k- minor of jacob(W), not identically zero
1694                      //k=n-dim(W)
1695      V=L[3];  //the elements of W corresponding to m
1696      v=L[4];  //the indices of variables corresponding to m
1697      w=L[5];  //the indices of variables not corresponding to m
1698
1699//--- Step 2
1700//--- first some initialization depending on results of step 1
1701      k=size(V);
1702      matrix dg[1][k];
1703      matrix df[k][1];
1704//--- derivatives of the generators of J w.r.t. system of parameters
1705      for(i=1;i<=size(J);i++)
1706      {
1707         for(j=1;j<=n-k;j++)
1708         {
1709            for(l=1;l<=k;l++)
1710            {
1711               dg[1,l]=diff(V[l],var(w[j]));
1712               df[l,1]=diff(J[i],var(v[l]));
1713             }
1714             C=C,m*diff(J[i],var(w[j]))-dg*A*df;
1715         }
1716      }
1717//--- everything should live in W, not just in the intersection of
1718//--- D(m) with W
1719      C=C+W;
1720      C=sat(C,m)[1];
1721//--- intersect ideal with previously computed ones to make sure that no
1722//--- components are lost
1723      D=intersect(D,C);
1724      kill dg,df,A;
1725   }
1726//--- return minimal set of generators of the result
1727   list li=mstd(D);
1728   D=li[2];
1729   if(size(li[1])<=size(D)){D=li[1];}
1730   return(D);
1731}
1732example
1733{ "EXAMPLE:";
1734   echo = 2;
1735   ring R=0,(x,y,z),dp;
1736
1737   ideal W=z^2-x;
1738   ideal J=x*y^2+x^3;
1739   intvec b=1;
1740   list E;
1741   ideal abb=maxideal(1);
1742   intvec v;
1743   intvec w=-1;
1744   matrix M;
1745
1746   list BO=W,J,b,E,abb,v,w,M;
1747
1748   Delta(BO);
1749}
1750
1751//////////////////////////////////////////////////////////////////////////////
1752static
1753proc redMax(int k,ideal J)
1754"Internal procedure - no help and no example available
1755"
1756{
1757//--- reduce maxideal(k) by J, more efficient approach
1758    int i;
1759    ideal K=simplify(reduce(maxideal(1),J),2);
1760    for(i=2;i<=k;i++)
1761    {
1762       K=simplify(reduce(K*maxideal(1),J),2);
1763    }
1764    return(K);
1765}
1766
1767//////////////////////////////////////////////////////////////////////////////
1768static
1769proc findMinor(ideal W)
1770"Internal procedure - no help and no example available
1771"
1772{
1773//---------------------------------------------------------------------------
1774// Initialization and sanity checks
1775//---------------------------------------------------------------------------
1776   list L;
1777   intvec v,w;
1778   ideal Wstd=std(W);
1779   int n=nvars(basering);   // total number of columns of Jacobian
1780   int k=n-dim(Wstd);       // size of minors of Jacobian
1781   int a=size(W);           // total number of rows of Jacobian
1782   matrix A[k][k];
1783   list LW=indexSet(a,k);   // set of tuples of k rows
1784   list LV=indexSet(n,k);   // set of tuples of k columns
1785   ideal IW,IV;
1786   int i,j,l,e;
1787   list re;
1788//---------------------------------------------------------------------------
1789// We need to know which minor corresponds to which variable and to which
1790// generator of W - therefore we cannot use the function minor()!
1791//---------------------------------------------------------------------------
1792//--- choose the generators which we want to differentiate
1793   for(i=1;i<=size(LW);i++)
1794   {
1795      IW=0;
1796      for(l=1;l<=a;l++)
1797      {
1798         if(LW[i][l]!=0){IW[size(IW)+1]=W[l];}
1799      }
1800//--- choose the variables by which to differentiate and apply diff
1801      for(j=1;j<=size(LV);j++)
1802      {
1803          IV=0;v=0;w=0;
1804          for(l=1;l<=n;l++)
1805          {
1806             if(LV[j][l]!=0)
1807             {
1808                v[size(v)+1]=l;
1809                IV[size(IV)+1]=var(l);
1810             }
1811             else
1812             {
1813                w[size(w)+1]=l;
1814
1815             }
1816          }
1817          A=diff(IV,IW);      // appropriate submatrix of Jacobian
1818//--- if the minor is non-zero, then it might be the one we need
1819//--- ==> put it in the list of candidates
1820          if(det(A)!=0)
1821          {
1822            v=v[2..size(v)];  // first entry is zero for technical reasons
1823            w=w[2..size(w)];  // first entry is zero for technical reasons
1824            L=inverse_L(A);
1825            L[3]=IW;
1826            L[4]=v;
1827            L[5]=w;
1828            re[size(re)+1]=L;
1829          }
1830      }
1831   }
1832//---------------------------------------------------------------------------
1833// return the result
1834//---------------------------------------------------------------------------
1835   return(re);
1836}
1837
1838/////////////////////////////////////////////////////////////////////////////
1839static
1840proc indexSet(int a, int b)
1841"Internal procedure - no help and no example available
1842"
1843{
1844//---------------------------------------------------------------------------
1845// Find all tuples of size b containing pairwise distict elements from a
1846// list of a elements
1847//---------------------------------------------------------------------------
1848//**************************************************************************/
1849// Combinatorics is expensive in an interpreted language
1850// ==> shift it into the kernel
1851//**************************************************************************/
1852   def R=basering;
1853   list L;
1854   ring S=2,x(1..a),dp;
1855   ideal I=maxideal(b);
1856   int i;
1857   ideal J=x(1)^2;
1858   for(i=2;i<=a;i++){J=J,x(i)^2;}
1859   attrib(J,"isSB",1);
1860   I=reduce(I,J);
1861   I=simplify(I,2);
1862   for(i=1;i<=size(I);i++){L[i]=leadexp(I[i]);}
1863   setring R;
1864   return(L);
1865}
1866
1867/////////////////////////////////////////////////////////////////////////////
1868
1869proc DeltaList(list BO)
1870"USAGE:  DeltaList (BO);
1871@*       BO = basic object, a list: ideal W,
1872@*                                  ideal J,
1873@*                                  intvec b,
1874@*                                  list Ex,
1875@*                                  ideal ab,
1876@*                                  intvec v,
1877@*                                  intvec w,
1878@*                                  matrix M
1879ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
1880@*       J  = ideal containing W
1881COMPUTE: Delta-operator iteratively applied to J in the notation of
1882         [Bravo,Encinas,Villamayor]
1883RETURN:  list l of length ((max w-ord) * b),
1884         l[i+1]=Delta^i(J)
1885EXAMPLE: example DeltaList;  shows an example
1886"
1887{
1888//----------------------------------------------------------------------------
1889// Iteratively apply proc Delta
1890//----------------------------------------------------------------------------
1891   int i;
1892   list L;
1893   ideal C=BO[2];
1894   while(deg(C[1])!=0)
1895   {
1896      L[size(L)+1]=C;
1897      C=Delta(BO);
1898      BO[2]=C;
1899   }
1900   return(L);
1901}
1902example
1903{
1904   "EXAMPLE:";
1905   echo = 2;
1906   ring R=0,(x,y,z),dp;
1907
1908   ideal W=z^2-x;
1909   ideal J=x*y^2+x^3;
1910   intvec b=1;
1911   list E;
1912   ideal abb=maxideal(1);
1913   intvec v;
1914   intvec w=-1;
1915   matrix M;
1916
1917   list BO=W,J,b,E,abb,v,w,M;
1918
1919   DeltaList(BO);
1920}
1921/////////////////////////////////////////////////////////////////////////////
1922proc CenterBM(list BM)
1923"USAGE:  CenterBM(BM);
1924@*       BM = object related to a presentation,
1925                            a list: ideal W,
1926@*                                  ideal J,
1927@*                                  intvec b,
1928@*                                  list Ex,
1929@*                                  ideal ab,
1930@*                                  intvec v,
1931@*                                  intvec w,
1932@*                                  matrix M
1933ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
1934@*       J  = ideal containing W
1935COMPUTE: the center of the next blow-up of BM in the resolution algorithm
1936         of [Bierstone, Milman]
1937RETURN:  list l,
1938         l[1]: ideal describing the center
1939         l[2]: intvec w obtained in the process of determining l[1]
1940         l[3]: intvec b obtained in the process of determining l[1]
1941         l[4]: intmat invmat obtained in the process of determining l[1]
1942EXAMPLE: example CenterBM;  shows an example
1943"
1944{
1945//!!! NOCH NICHT IN BETRIEB
1946ERROR("Not implemented yet");
1947   int i,j;
1948   intmat tmat[2][1]=0,-1;
1949//--- re=center,E^- indices, b vector, n vector
1950   list re=ideal(1),BM[7],BM[3],tmat;
1951   ideal J=BM[2];
1952   if(size(J)==0)
1953   {
1954     re[1]=ideal(0);
1955     return(re);
1956   }
1957//--- find Delta^(b-1)(J)
1958   if(size(reduce(J,std(BM[1])))!=0)
1959   {
1960     list L=DeltaList(BM);
1961   }
1962   else
1963   {
1964     list L;
1965     L[1]=J;
1966   }
1967   if(!defined(debugCenter))
1968   {
1969     int debugCenter;
1970   }
1971   if(debugCenter)
1972   {
1973     "----> In Center: after DeltaList";
1974     "W";
1975     BM[1];
1976     "J";
1977     BM[2];
1978     "The Delta List:";
1979     L;
1980   }
1981   int b=size(L);
1982   if(b==0)
1983   {
1984//--- if J=W, we do not need to do anything
1985//--- returning center=1 marks this chart as completed
1986     return(re);
1987   }
1988//---------------------------------------------------------------------------
1989// check whether max ord is constant
1990//---------------------------------------------------------------------------
1991   if((BM[9][2,1]<0)||(BM[9][1,1]>b))
1992   {
1993//--- we are either at the beginning or the invariant has dropped
1994     intvec tempvec=size(BM[4]);
1995     BM[7]=tempvec;
1996//!!!! nur fuer hyperflaechen!!!!!!!!
1997     tempvec=b;
1998     BM[3]=tempvec;
1999//!!!! Ende !!!!!!!!!!!!
2000     kill tempvec;
2001     BM[9][1,1]=b;
2002     BM[9][2,1]=1;
2003   }
2004//---------------------------------------------------------------------------
2005// prepare for intersection with E_i
2006//---------------------------------------------------------------------------
2007   ideal C=L[b];
2008   re[2]=BM[7];
2009   re[3]=BM[3];
2010   BM[2]=C;
2011      if(debugCenter)
2012   {
2013     "----> In Center: before intersection with E_i:";
2014     "bmax:",b;
2015     "Sing(J,bmax):";
2016      C;
2017     "E:";
2018      BO[4];
2019     "list marking a priori known intersection properties:",BO[6];
2020     "index of last element of E^- in E:",BO[7][1];
2021   }
2022   list E=inters_E(BM);
2023// !!!!!!!!! Drop Redundant fehlt noch!!!!!!!!
2024//---------------------------------------------------------------------------
2025// Check whether it is a single point
2026//---------------------------------------------------------------------------
2027   ideal C1=std(ideal(L[b])+E[1]);
2028   if(dim(C1)==0)
2029   {
2030     if(size(E[4])==1)
2031     {
2032        tmat[1,1]=BM[9][1,1];
2033        tmat[2,1]=BM[9][2,1];
2034        re[4]=tmat;
2035        re[1]=radical(C1);
2036        return(re);
2037     }
2038   }
2039   if(size(BM[9])>2)
2040   {
2041      BM[9][1,2]=E[2];
2042      BM[9][2,2]=1;
2043   }
2044   else
2045   {
2046      intmat tempInt[2][1]=E[2],1;
2047      BM[9]=concatInt(BM[9],tempInt);
2048      kill tempInt;
2049   }
2050   BM[2]=J;
2051   list BM1=dropDim(BM);
2052   list BMlist,hilfList;
2053   ideal hilf;
2054   intvec tempvec;
2055
2056   if(!attrib(BM1[1],"isSB")){BM1[1]=std(BM1[1]);}
2057   for(i=1;i<=size(BM1[4]);i++)
2058   {
2059      hilf=simplify(reduce(BM1[4][i],BM1[1]),2);
2060      if(size(hilf)>1){"Problem with BM1[4]in CenterBM";~;}
2061      hilfList[i]=hilf[1];
2062   }
2063   for(i=1;i<=size(E[4]);i++)
2064   {
2065      BMlist[i]=BM1;
2066      for(j=size(E[5][i]);j>=1;j--)
2067      {
2068         if(E[5][i][j]!=0)
2069         {
2070            BMlist[i][2][size(BMlist[i][2])+1]=hilfList[j];
2071            BMlist[i][3][size(BMlist[i][3])+1]=1;
2072         }
2073         BMlist[i][4]=delete(BMlist[i][4],j);
2074         BMlist[i][6]=deleteInt(BMlist[i][6],j,0);
2075      }
2076      BMlist[i][7]=deleteInt(BMlist[i][7],1,-1);
2077      if(size(BMlist[i][9])>4)
2078      {
2079         intmat tempInt[2][ncols(BMlist[i][9])]=BMlist[i][9];
2080         intmat tempInt2[2][ncols(BMlist[i][9])-2]=
2081                 tempInt[1..2,3..ncols(BMlist[i][9])];
2082         BMlist[i][9]=tempInt2;
2083         kill tempInt,tempInt2;
2084      }
2085      else
2086      {
2087         BMlist[i][9]=tmat;
2088      }
2089   }
2090   kill hilfList;list hilfList;
2091   hilfList[1]=CenterTail(BMlist[1],C);
2092   intmat maxmat=hilfList[1][9];
2093   intvec maxiv=E[4][1];
2094   int pos=1;
2095   for(i=2;i<=size(E[4]);i++)
2096   {
2097      hilfList[i]=CenterTail(BMlist[i],C);
2098      if(invGreater(hilfList[i][4]),maxmat,E[4][i],maxiv)
2099      {
2100         maxmat=hilfList[i][4];
2101         maxiv=E[4][i];
2102         pos=i;
2103      }
2104   }
2105   re[1]=hilfList[pos][1];
2106   intmat tempint=BM[9];
2107   intmat tempint1[2][2]=tempint[1..2,1..2];
2108   re[4]=concatInt(tempint1,maxmat);
2109   re[2]=re[2][1],hilfList[pos][2];
2110   re[3]=b;
2111~;
2112   return(re);
2113}
2114example
2115{  "EXAMPLE:";
2116   echo = 2;
2117   ring R=0,(x,y),dp;
2118
2119   ideal W;
2120   ideal J=x2-y3;
2121   intvec b=1;
2122   list E;
2123   ideal abb=maxideal(1);
2124   intvec v;
2125   intvec w=-1;
2126   matrix M;
2127   intmat invmat[2][1]=0,-1;
2128
2129   list BM=W,J,b,E,abb,v,w,M,invmat;
2130
2131   CenterBM(BM);
2132}
2133
2134/////////////////////////////////////////////////////////////////////////////
2135static
2136proc invGreater(intmat M1, intmat M2, intvec iv1, intvec iv2)
2137{
2138// Auxilliary procedure, BM-algorithm
2139   int i;
2140   for(i=1;i<=min(ncols(M1),ncols(M2));i++)
2141   {
2142      if(M1[2,i]==-1)
2143      {
2144         if(M1[1,i]==0){ERROR("Invariant not set");}
2145         if(M2[2,i]!=-1){return(1);}
2146         if(M2[1,i]==0){ERROR("Invariant not set");}
2147         break;
2148      }
2149      else
2150      {
2151         if(M2[2,i]==-1)
2152         {
2153            if(M2[1,i]==0){ERROR("Invariant not set");}
2154            return(0);
2155         }
2156         if(M1[1,i]*M2[2,i]!= M2[1,i]*M1[2,i])
2157         {
2158            return(M1[1,i]*M2[2,i]> M2[1,i]*M1[2,i]);
2159         }
2160      }
2161   }
2162   return(iv1>iv2);
2163}
2164/////////////////////////////////////////////////////////////////////////////
2165proc CenterTail(list BM, ideal C)
2166{
2167//!!! Auxilliary procedure, BM-algorithm
2168//!!!!!!!!Rueckgabe im Zentrumsformat
2169  int i,j,bmin;
2170  int alpha=lcm(BM[3]);
2171  vector w;
2172  list re;
2173  if(size(BM[2])==0)
2174  {
2175    re[1]=C+BM[1];
2176    intvec tvec;
2177    re[3]=tvec;
2178    intmat tmat[2][1]=-1,-1;
2179    re[4]=tmat;
2180    tvec=size(BM[4]);
2181    re[2]=tvec;
2182    return(re);
2183  }
2184  for(i=1;i<=size(BM[3]);i++)
2185  {
2186     if(BM[2][i]!=0)
2187     {
2188       w[size(w)+1]=BM[2][i]^(alpha/BM[3][i]);
2189     }
2190  }
2191  module M=w;
2192  intvec satex;
2193  list satList;
2194  for(i=1;i<=size(BM[4]);i++)
2195  {
2196     satList=sat(M,BM[4][i]);
2197     satex[i]=satList[2];
2198     M=satList[1];
2199  }
2200//!!!!Hilfsobjekt G bilden!!!!!!!!!!!!!!!!
2201//!!!!Hilfsobjekt H,codim -1 bilden!!!!!!!!!!!!!!!!
2202//!!!! ???? an welcher stelle?????????
2203  list deltaL;
2204  list BMtemp=BM;
2205  for(i=1;i<=nrows(M[1]);i++)
2206  {
2207     BMtemp[2]=ideal(M[1][i])+BMtemp[1];
2208     deltaL[i]=DeltaList(BMtemp);
2209     if(i==1)
2210     {
2211        bmin=size(deltaL[i]);
2212     }
2213     else
2214     {
2215        bmin=min(size(deltaL[i]),bmin);
2216     }
2217  }
2218  if(bmin==0)
2219  {
2220     re[1]=C+BM[1];
2221     intvec tvec;
2222     re[3]=tvec;
2223     if((BM[9][2,1]==-1)||(BM[9][1,1]!=0))
2224     {
2225        tvec=size(BM[4]);
2226        re[2]=tvec;
2227        intmat tmat[2][1]=0,1;
2228        re[4]=tmat;
2229     }
2230     else
2231     {
2232        re[2]=BM[7];
2233        re[4]=BM[9];
2234     }
2235     return(re);
2236  }
2237  ideal Ctemp=ideal(1);
2238  while(deg(Ctemp[1])==0)
2239  {
2240    Ctemp=C;
2241    for(i=1;i<=nrows(M[1]);i++)
2242    {
2243       Ctemp=Ctemp,deltaL[i][bmin];
2244    }
2245    Ctemp=std(Ctemp);
2246    bmin--;
2247    if(bmin==0){ERROR("empty set");}
2248  }
2249  //!!!!!!!!!!!!!Invariante ist bmin/alpha
2250  // naechster Eintrag s_i wie in CenterBM
2251  // dann dropDim  ....
2252}
2253
2254/////////////////////////////////////////////////////////////////////////////
2255static
2256proc deleteInt(intvec v,int i,int ini)
2257{
2258//!!! Should be in kernel of Singular
2259//--- delete i-th entry in intvec v,
2260//--- if necessary reinitializing v with value ini
2261   int s=size(v);
2262   intvec w;
2263   if((i<s)&&(i>1)){w=v[1..i-1],v[i+1..s];}
2264   if(s==1){w=ini;return(w);}
2265   if(i==1){w=v[2..s];}
2266   if(i==s){w=v[1..s-1];}
2267   return(w);
2268}
2269/////////////////////////////////////////////////////////////////////////////
2270static
2271proc concatInt(intmat A, intmat B)
2272{
2273//!!! Should be in kernel of Singular
2274//--- concatenate two intmats
2275  if(nrows(A)!=nrows(B)){ERROR("could not concat, wrong number of rows");}
2276  intmat tempmat[nrows(A)][ncols(A)+ncols(B)];
2277  tempmat[1..nrows(A),1..ncols(A)]=A[1..nrows(A),1..ncols(A)];
2278  tempmat[1..nrows(A),ncols(A)+1..ncols(tempmat)]=B[1..nrows(A),1..ncols(B)];
2279  return(tempmat);
2280}
2281/////////////////////////////////////////////////////////////////////////////
2282proc dropDim(list BM)
2283{
2284ERROR("Not implemented yet");
2285}
2286/////////////////////////////////////////////////////////////////////////////
2287proc CenterBO(list BO,list #)
2288"USAGE:  CenterBO(BO);
2289@*       BO = basic object, a list: ideal W,
2290@*                                  ideal J,
2291@*                                  intvec b,
2292@*                                  list Ex,
2293@*                                  ideal ab,
2294@*                                  intvec v,
2295@*                                  intvec w,
2296@*                                  matrix M
2297ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
2298@*       J  = ideal containing W
2299COMPUTE: the center of the next blow-up of BO in the resolution algorithm
2300         of [Bravo,Encinas,Villamayor]
2301RETURN:  list l,
2302         l[1]: ideal describing the center
2303         l[2]: intvec w obtained in the process of determining l[1]
2304         l[3]: intvec b obtained in the process of determining l[1]
2305         l[4]: intvec inv obtained in the process of determining l[1]
2306EXAMPLE: example CenterBO;  shows an example
2307"
2308{
2309//---------------------------------------------------------------------------
2310// Initialization  and sanity checks
2311//---------------------------------------------------------------------------
2312   int i,bo7save;
2313   intvec tvec;
2314//--- re=center,E^- indices, b vector, n vector
2315   list re=ideal(1),BO[7],BO[3],tvec;
2316   ideal J=BO[2];
2317   if(size(J)==0)
2318   {
2319     re[1]=ideal(0);
2320     return(re);
2321   }
2322//--- find Delta^(b-1)(J)
2323   if(size(reduce(J,std(BO[1])))!=0)
2324   {
2325     list L=DeltaList(BO);
2326   }
2327   else
2328   {
2329     list L;
2330     L[1]=J;
2331   }
2332   if(!defined(debugCenter))
2333   {
2334     int debugCenter;
2335   }
2336   if(debugCenter)
2337   {
2338     "----> In Center: after DeltaList";
2339     "W";
2340     BO[1];
2341     "J";
2342     BO[2];
2343     "The Delta List:";
2344     L;
2345   }
2346   int b=size(L);
2347   if(b==0)
2348   {
2349//--- if J=W, we do not need to do anything
2350//--- returning center=1 marks this chart as completed
2351     return(re);
2352   }
2353//---------------------------------------------------------------------------
2354// check whether max w-ord is constant
2355//---------------------------------------------------------------------------
2356   if(b==BO[3][1])
2357   {
2358//--- max w-ord is constant
2359     if(BO[7][1]==-1)
2360     {
2361//--- first got its value in the previous step ==> initialize BO[7]
2362       tvec[1]=size(BO[4])-1;
2363       for(i=2;i<=size(BO[7]);i++)
2364       {
2365         tvec[i]=BO[7][i];
2366       }
2367       re[2]=tvec;
2368       BO[7]=tvec;
2369     }
2370   }
2371   else
2372   {
2373//--- max w-ord changed ==> reset BO[7], correct BO[3]
2374     tvec[1]=-1;
2375     re[2]=tvec;
2376     BO[7]=tvec;
2377     tvec[1]=b;
2378     BO[3]=tvec;
2379     if(defined(invSat))
2380     {
2381        invSat[2]=intvec(0);
2382     }
2383   }
2384   re[3]=BO[3];
2385//---------------------------------------------------------------------------
2386// reduce from case 2 to case 1 of [Bravo, Encinas, Villamayor]
2387//---------------------------------------------------------------------------
2388   ideal C=L[b];
2389   BO[2]=C;
2390   if(debugCenter)
2391   {
2392     "----> In Center: before intersection with E_i:";
2393     "bmax:",b;
2394     "Sing(J,bmax):";
2395      C;
2396     "E:";
2397      BO[4];
2398     "list marking a priori known intersection properties:",BO[6];
2399     "index of last element of E^- in E:",BO[7][1];
2400   }
2401//--- is intermediate result in iteration already good?
2402//--- return it to calling proc CenterBO
2403   if(size(#)>0)
2404   {
2405     if(#[1]==2)
2406     {
2407       re[1]=C;
2408       kill tvec;
2409       intvec tvec=re[2][1];
2410       re[2]=tvec;
2411       kill tvec;
2412       intvec tvec=re[3][1];
2413       re[3]=tvec;
2414       kill tvec;
2415       intvec tvec;
2416       re[4]=tvec;
2417       return(re);
2418     }
2419   }
2420//--- do the reduction to case 1
2421   list E=inters_E(BO);
2422//--- if J is smooth and not too many E_i intersect simultaneously, let us
2423//--- try to drop redundant components of the candidate for the center
2424   if((b==1)&&(size(E)>3))
2425   {
2426//--- if J is not smooth we do not want to drop any information
2427     if((size(E[4])>0) && (dim(std(slocusE(BO[2])))<0))
2428     {
2429//--- BO[2]==J because b==1
2430//--- DropRedundant is the counterpart to DropCoeff
2431//--- do not leave out one of them separately!!!
2432      E=DropRedundant(BO,E);
2433      if(size(E)==1)
2434       {
2435         kill tvec;
2436         intvec tvec=re[2][1];
2437         re[2]=tvec;
2438         tvec[1]=re[3][1];
2439         re[3]=tvec;
2440         tvec[1]=re[4][1];
2441         re[4]=tvec;
2442         re[1]=E[1];
2443         return(re);
2444       }
2445     }
2446   }
2447//--- set n correctly
2448   if(E[2]<BO[9][1])
2449   {
2450//--- if n dropped, the subsequent Coeff-object will not be the same
2451//--- ===> set BO[3][2] to zero to make sure that no previous data is used
2452      if(defined(tvec)) {kill tvec;}
2453      intvec tvec=BO[7][1],-1;
2454      BO[7]=tvec;
2455      tvec=BO[3][1],0;
2456      BO[3]=tvec;
2457      if(defined(invSat))
2458      {
2459         invSat[2]=intvec(0);
2460      }
2461   }
2462   re[4][1]=E[2];
2463   C=E[1]^b+J;
2464   C=mstd(C)[2];
2465   ideal C1=std(ideal(L[b])+E[1]);
2466   if(debugCenter)
2467   {
2468     "----> In Center: reduction of case 2 to case 1";
2469     "Output of inters_E, after dropping redundant components:";
2470      E;
2471     "result of intersection with E^-, i.e.(E^-)^b+J:";
2472     C;
2473     "candidate for center:";
2474     C1;
2475   }
2476//---------------------------------------------------------------------------
2477// Check whether we have a hypersurface component
2478//---------------------------------------------------------------------------
2479   if(dim(C1)==dim(std(BO[1]))-1)
2480   {
2481     if((size(reduce(J,C1))==0)&&(size(reduce(C1,std(J)))==0))
2482     {
2483//--- C1 equals J and is of codimension 1 in W
2484        re[1]=C1;
2485     }
2486     else
2487     {
2488//--- C1 has a codimension 1 (in W) component
2489        re[1]=std(equiRadical(C1));
2490     }
2491     kill tvec;
2492     intvec tvec=re[2][1];
2493     re[2]=tvec;
2494     tvec[1]=re[3][1];
2495     re[3]=tvec;
2496     tvec[1]=re[4][1];
2497     re[4]=tvec;
2498//--- is the codimension 1 component a good choice or do we need to reset
2499//--- the information from the previous steps
2500     if(transversalT(re[1],BO[4]))
2501     {
2502        if(size(E)>2)
2503        {
2504          if(E[3]>E[2])
2505          {
2506            if(defined(shortcut)){kill shortcut;}
2507            list shortcut=ideal(0),size(BO[4]),BO[7];
2508            export(shortcut);
2509          }
2510        }
2511        return(re);
2512     }
2513
2514     ERROR("reset in Center, please send the example to the authors.");
2515   }
2516//---------------------------------------------------------------------------
2517// Check whether it is a single point
2518//---------------------------------------------------------------------------
2519   if(dim(C1)==0)
2520   {
2521      C1=std(radical(C1));
2522      if(vdim(C1)==1)
2523      {
2524//--- C1 is one point
2525        re[1]=C1;
2526        kill tvec;
2527        intvec tvec=re[2][1];
2528        re[2]=tvec;
2529        kill tvec;
2530        intvec tvec=re[3][1];
2531        re[3]=tvec;
2532        return(re);
2533      }
2534    }
2535//---------------------------------------------------------------------------
2536// Prepare input for forming the Coeff-Ideal
2537//---------------------------------------------------------------------------
2538   BO[2]=C;
2539   if(size(BO[2])>5)
2540   {
2541      BO[2]=mstd(BO[2])[2];
2542   }
2543//--- drop leading entry of BO[3]
2544   tvec=BO[3];
2545   if(size(tvec)>1)
2546   {
2547     tvec=tvec[2..size(tvec)];
2548     BO[3]=tvec;
2549   }
2550   else
2551   {
2552     BO[3][1]=0;
2553   }
2554   tvec=BO[9];
2555   if(size(tvec)>1)
2556   {
2557     tvec=tvec[2..size(tvec)];
2558     BO[9]=tvec;
2559   }
2560   else
2561   {
2562     BO[9][1]=0;
2563   }
2564   bo7save=BO[7][1];          // original value needed for result
2565   if(defined(shortcut))
2566   {
2567     if((bo7save!=shortcut[3][1])&&(size(shortcut[3])!=1))
2568     {
2569       kill shortcut;
2570     }
2571     else
2572     {
2573       shortcut[2]=shortcut[2]-bo7save;
2574       tvec=shortcut[3];
2575       if(size(tvec)>1)
2576       {
2577         tvec=tvec[2..size(tvec)];
2578         shortcut[3]=tvec;
2579       }
2580       else
2581       {
2582         shortcut[3]=intvec(shortcut[2]);
2583       }
2584     }
2585   }
2586   if(BO[7][1]>-1)
2587   {
2588//--- drop E^- and the corresponding information from BO[6]
2589     for(i=1;i<=BO[7][1];i++)
2590     {
2591       BO[4]=delete(BO[4],1);
2592       intvec bla1=BO[6];
2593       BO[6]=intvec(bla1[2..size(bla1)]);
2594       kill bla1;
2595     }
2596//--- drop leading entry of BO[7]
2597     tvec=BO[7];
2598     if(size(tvec)>1)
2599     {
2600       tvec=tvec[2..size(tvec)];
2601       BO[7]=tvec;
2602     }
2603     else
2604     {
2605       BO[7][1]=-1;
2606     }
2607   }
2608   else
2609   {
2610     if(BO[7][1]==-1)
2611     {
2612       list tplist;
2613       BO[4]=tplist;
2614       kill tplist;
2615     }
2616   }
2617   if(debugCenter)
2618   {
2619     "----> In Center: Input to Coeff";
2620     "b:",b;
2621     "BO:";
2622     BO;
2623   }
2624//--- prepare the third entry of the invariant tuple
2625   int invSatSave=invSat[2][1];
2626   tvec=invSat[2];
2627   if(size(tvec)>1)
2628   {
2629     tvec=tvec[2..size(tvec)];
2630     invSat[2]=tvec;
2631   }
2632   else
2633   {
2634     invSat[2][1]=0;
2635   }
2636//---------------------------------------------------------------------------
2637// Form the Coeff-ideal, if possible and useful; otherwise use the previous
2638// candidate for the center
2639//---------------------------------------------------------------------------
2640   list BO1=Coeff(BO,b);
2641   if(debugCenter)
2642   {
2643     "----> In Center: Output of Coeff";
2644     BO1;
2645   }
2646//--- Coeff returns int if something went wrong
2647   if(typeof(BO1[1])=="int")
2648   {
2649      if(BO1[1]==0)
2650      {
2651//--- Coeff ideal was already resolved
2652        re[1]=C1;
2653        return(re);
2654      }
2655      else
2656      {
2657//--- no global hypersurface found
2658        re=CoverCenter(BO,b,BO1[2]);
2659        kill tvec;
2660        intvec tvec=invSatSave;
2661        for(i=1;i<=size(invSat[2]);i++)
2662        {
2663           tvec[i+1]=invSat[2][i];
2664        }
2665        invSat[2]=tvec;
2666        return(re);
2667      }
2668   }
2669   int coeff_invar;
2670   ideal Idropped=1;
2671//--- if b=1 drop redundant components of the Coeff-ideal
2672   if(b==1)
2673   {
2674//--- Counterpart to DropRedundant -- do not leave out one of them separately
2675     Idropped=DropCoeff(BO1);         // blow-up in these components
2676                                      // is unnecessary
2677   }
2678//--- to switch off DropCoeff, set Idropped=1;
2679   BO1[2]=sat(BO1[2],Idropped)[1];
2680   if(deg(BO1[2][1])==0)
2681   {
2682//--- Coeff ideal is trivial
2683     C1=radical(C1);
2684     ideal C2=sat(C1,Idropped)[1];
2685     if(deg(std(C2)[1])!=0)
2686     {
2687        C1=C2;
2688     }
2689//Aenderung: Strategie: nur im Notfall ganze except. Divisoren
2690     if(deg(std(BO1[2])[1])==0)
2691     {
2692       list BOtemp=BO;
2693       int bo17save=BO1[7][1];
2694       BOtemp[7]=0;
2695       BO1=Coeff(BOtemp,b,int(0));
2696       BO1[2]=sat(BO1[2],Idropped)[1];
2697       if(deg(std(BO1[2])[1])==0)
2698       {
2699//--- there is really nothing left to do for the Coeff ideal
2700//--- the whole original BO1[2], i.e. Idropped, is the upcoming center
2701          re[1]=Idropped;
2702          re[2]=intvec(bo7save);
2703          re[3]=intvec(b);
2704          re[4]=intvec(E[2]);
2705          return(re);
2706       }
2707       if(deg(std(slocus(radical(BO1[2])))[1])==0)
2708       {
2709          re[1]=BO1[2];
2710//          re[2]=intvec(bo7save,BO1[7][1]);
2711          re[2]=intvec(bo7save,bo17save);
2712          re[3]=intvec(b,1);
2713          re[4]=intvec(E[2],1);
2714          invSat[2]=intvec(1,0);
2715          return(re);
2716       }
2717//!!! effizienter machen???
2718       list pr=primdecGTZ(BO1[2]);
2719       ideal Itemp1=1;
2720       int aa,bb;
2721       for(aa=1;aa<=size(pr);aa++)
2722       {
2723          if(dim(std(pr[aa][2])) < (dim(std(BO1[1]))-1))
2724          {
2725//--- drop components which are themselves exceptional diviosrs
2726             Itemp1=intersect(Itemp1,pr[aa][1]);
2727          }
2728       }
2729       if(deg(std(Itemp1)[1])!=0)
2730       {
2731//--- treat the remaining components of the weak Coeff ideal
2732          BO1[2]=Itemp1;
2733       }
2734       BO1[7]=BO[7];
2735       for(aa=1;aa<=size(BO1[4]);aa++)
2736       {
2737         if(deg(std(BO1[4][aa])[1])==0){aa++;continue;}
2738         if(defined(satlist)){kill satlist;}
2739         list satlist=sat(BO1[2],BO1[4][aa]+BO1[1]);
2740         if(deg(std(satlist[1])[1])==0)
2741         {
2742            coeff_invar++;
2743            if(satlist[2]!=0)
2744            {
2745              for(bb=1;bb<=satlist[2]-1;bb++)
2746              {
2747                 BO1[2]=quotient(BO1[2],BO1[4][aa]+BO1[1]);
2748              }
2749            }
2750            else
2751            {
2752              ERROR("J of temporary object had unexpected value;
2753                     please send this example to the authors.");
2754            }
2755         }
2756         else
2757         {
2758            BO1[2]=satlist[1];
2759         }
2760       }
2761       if(deg(std(Itemp1)[1])==0)
2762       {
2763          re[1]=BO1[2];
2764          re[2]=intvec(bo7save,BO1[7][1]);
2765          re[3]=intvec(b,1);
2766          re[4]=intvec(E[2],1);
2767          invSat[2]=intvec(1,0);
2768          return(re);
2769       }
2770       kill aa,bb;
2771     }
2772   }
2773   if(invSatSave<coeff_invar)
2774   {
2775     invSatSave=coeff_invar;
2776   }
2777//---------------------------------------------------------------------------
2778// Determine Center of Coeff-ideal and use it as the new center
2779//---------------------------------------------------------------------------
2780   if(!defined(templist))
2781   {
2782     if(size(BO1[2])>5)
2783     {
2784        BO1[2]=mstd(BO1[2])[2];
2785     }
2786     list templist=CenterBO(BO1,2);
2787//--- only a sophisticated guess of a good center computed by
2788//--- leaving center before intersection with the E_i.
2789//--- whether the guess was good, is stored in 'good'.
2790//--- (this variant saves charts in cases like the Whitney umbrella)
2791     list E0,E1;
2792
2793     ideal Cstd=std(radical(templist[1]));
2794     int good=((deg(std(slocusE(Cstd))[1])==0)&&(dim(std(BO1[2]))<=2));
2795//if(defined(satlist)){good=0;}
2796     if(good)
2797     {
2798        for(i=1;i<=size(BO[4]);i++)
2799        {
2800           if((deg(BO[4][i][1])>0)&&(size(reduce(BO[4][i],Cstd))!=0))
2801           {
2802              E0[size(E0)+1]=BO[4][i]+Cstd;
2803              E1[size(E1)+1]=BO[4][i];
2804           }
2805        }
2806        good=transversalT(Cstd,E1);
2807        if(good)
2808        {
2809           good=normalCross(E0);
2810        }
2811     }
2812     if(good)
2813     {
2814        list templist2=CenterBO(BO1,1);
2815        if(dim(std(templist2[1]))!=dim(Cstd))
2816        {
2817           templist[1]=Cstd;
2818           if(defined(shortcut)){kill shortcut;}
2819           list shortcut=ideal(0),size(BO1[4]),templist[2];
2820           export(shortcut);
2821        }
2822        else
2823        {
2824           templist=templist2;
2825        }
2826        kill templist2;
2827     }
2828     else
2829     {
2830//--- sophisticated guess was wrong, follow Villamayor's approach
2831        kill templist;
2832        list templist=CenterBO(BO1,1);
2833     }
2834   }
2835   if((dim(std(templist[1]))==dim(std(BO1[1]))-1)
2836       &&(size(templist[4])==1))
2837   {
2838     if(templist[4][1]==0)
2839     {
2840        for(i=1;i<=size(BO1[4]);i++)
2841        {
2842           if(size(reduce(templist[1],std(BO1[4][i])))==0)
2843           {
2844              templist[4][1]=1;
2845              break;
2846           }
2847        }
2848     }
2849   }
2850//!!! subsequent line should be deleted
2851//if(defined(satlist)){templist[3][1]=BO[3][1];}
2852   if(debugCenter)
2853   {
2854     "----> In Center: Iterated Center returned:";
2855     templist;
2856   }
2857//--------------------------------------------------------------------------
2858// set up the result and return it
2859//--------------------------------------------------------------------------
2860   re[1]=templist[1];
2861   kill tvec;
2862   intvec tvec;
2863   tvec[1]=bo7save;
2864   for(i=1;i<=size(templist[2]);i++)
2865   {
2866     tvec[i+1]=templist[2][i];
2867   }
2868   re[2]=tvec;
2869   if(defined(shortcut))
2870   {
2871      shortcut[2]=shortcut[2]+bo7save;
2872      shortcut[3]=tvec;
2873   }
2874   kill tvec;
2875   intvec tvec;
2876   tvec[1]=invSatSave;
2877   for(i=1;i<=size(invSat[2]);i++)
2878   {
2879      tvec[i+1]=invSat[2][i];
2880   }
2881   invSat[2]=tvec;
2882   kill tvec;
2883   intvec tvec;
2884   tvec[1]=b;
2885   for(i=1;i<=size(templist[3]);i++)
2886   {
2887     tvec[i+1]=templist[3][i];
2888   }
2889   re[3]=tvec;
2890   kill tvec;
2891   intvec tvec;
2892   tvec[1]=E[2];
2893   for(i=1;i<=size(templist[4]);i++)
2894   {
2895     tvec[i+1]=templist[4][i];
2896   }
2897   re[4]=tvec;
2898
2899   return(re);
2900}
2901example
2902{  "EXAMPLE:";
2903   echo = 2;
2904   ring R=0,(x,y),dp;
2905
2906   ideal W;
2907   ideal J=x2-y3;
2908   intvec b=1;
2909   list E;
2910   ideal abb=maxideal(1);
2911   intvec v;
2912   intvec w=-1;
2913   matrix M;
2914
2915   list BO=W,J,b,E,abb,v,w,M,v;
2916
2917   CenterBO(BO);
2918}
2919//////////////////////////////////////////////////////////////////////////////
2920static
2921proc CoverCenter(list BO,int b, ideal Jb)
2922{
2923//----------------------------------------------------------------------------
2924// Initialization
2925//----------------------------------------------------------------------------
2926   def R=basering;
2927   int i,j,k;
2928   intvec merk,merk2,maxv,fvec;
2929   list L,ceList,re;
2930   ceList[1]=ideal(0);
2931   poly @p,@f;
2932   ideal K,dummy;
2933   if(!attrib(BO[2],"isSB"))
2934   {
2935     BO[2]=std(BO[2]);
2936   }
2937   for(i=1;i<=size(Jb);i++)
2938   {
2939      list tempmstd=mstd(slocus(Jb[i]));
2940      if(size(tempmstd[1])>size(tempmstd[2]))
2941      {
2942         dummy=tempmstd[2];
2943      }
2944      else
2945      {
2946         dummy=tempmstd[1];
2947      }
2948      kill tempmstd;
2949      L[i]=dummy;
2950      K=K,dummy;
2951   }
2952   K=simplify(K,2);
2953//---------------------------------------------------------------------------
2954// The intersection of the singular loci of the L[i] is empty.
2955// Find a suitable open covering of the affine chart, such that a global
2956// hypersurface can be found in each open set.
2957//---------------------------------------------------------------------------
2958   matrix M=lift(K,ideal(1));
2959   j=1;
2960   for(i=1;i<=nrows(M);i++)
2961   {
2962      if(M[i,1]!=0)
2963      {
2964         merk[size(merk)+1]=i;
2965         fvec[size(merk)]=j;
2966      }
2967      if((i-k)==size(L[j]))
2968      {
2969        k=i;
2970        j++;
2971      }
2972   }
2973//--------------------------------------------------------------------------
2974// Find a candidate for the center in each open set
2975//--------------------------------------------------------------------------
2976//--- first entry of merk is 0 by construction of merk
2977   for(i=2;i<=size(merk);i++)
2978   {
2979//--- open set is D(@p)
2980       @p=K[merk[i]];
2981//--- hypersurface is V(@f)
2982       @f=Jb[fvec[i]];
2983       execute("ring R1=("+charstr(R)+"),(@y,"+varstr(R)+"),dp;");
2984       poly p=imap(R,@p);
2985       poly f=imap(R,@f);
2986       list @ce;
2987       list BO=imap(R,BO);
2988       BO[1]=BO[1]+ideal(@y*p-1);
2989       BO[2]=BO[2]+ideal(@y*p-1);
2990       for(j=1;j<=size(BO[4]);j++)
2991       {
2992          BO[4][j]=BO[4][j]+ideal(@y*p-1);
2993       }
2994//--- like usual Coeff, but hypersurface is already known
2995       list BO1=SpecialCoeff(BO,b,f);
2996//--- special situation in SpecialCoeff are marked by an error code of
2997//--- type int
2998       if(typeof(BO1[1])=="int")
2999       {
3000         if(BO1[1]==0)
3001         {
3002//--- Coeff ideal was already resolved
3003           @ce[1]=BO[2];
3004           @ce[2]=BO[7];
3005           @ce[3]=BO[3];
3006         }
3007         else
3008         {
3009           if(BO[3]!=0)
3010           {
3011//--- intersections with E do not meet conditions ==> reset
3012              ERROR("reset in Coeff, please send the example to the autors");
3013           }
3014         }
3015       }
3016       else
3017       {
3018//--- now do the recursion as usual
3019         @ce=CenterBO(BO1);
3020       }
3021//---------------------------------------------------------------------------
3022// Go back to the whole affine chart and form a suitable union of the
3023// candidates
3024//---------------------------------------------------------------------------
3025//--- pass from open set to the whole affine chart by taking the closure
3026       @ce[1]=eliminate(@ce[1],@y);
3027       setring R;
3028       ceList[i]=imap(R1,@ce);
3029//--- set up invariant vector and determine maximum value of it
3030       if(size(ceList[i][3])==size(ceList[i][4]))
3031       {
3032          kill merk2,maxv;
3033          intvec merk2,maxv;
3034          for(j=1;j<=size(ceList[i][3]);j++)
3035          {
3036            merk2[2*j-1]=ceList[i][3][j];
3037            merk2[2*j]=ceList[i][4][j];
3038            ceList[i][5]=merk2;
3039            if(maxv<merk2)
3040            {
3041               maxv=merk2;
3042            }
3043          }
3044       }
3045       else
3046       {
3047          ERROR("This situation should not occur, please send the example
3048                 to the authors.");
3049       }
3050       kill R1;
3051   }
3052   kill merk2;
3053   intvec merk2=-2;
3054//--- form the union of the components of the center with maximum invariant
3055   for(i=1;i<=size(ceList);i++)
3056   {
3057     if(size(reduce(ceList[i][1],BO[2]))==0)
3058     {
3059//--- already resolved ==> ignore
3060       i++;
3061       continue;
3062     }
3063     if(ceList[i][5]==maxv)
3064     {
3065        if(merk2!=ceList[i][2])
3066        {
3067//--- E^- not of the same size as before resp. initialization
3068          if(merk2[1]==-2)
3069          {
3070//--- initialization: save size of E^-
3071            merk2=ceList[i][2];
3072            re[1]=ceList[i][1];
3073            re[2]=ceList[i][2];
3074            re[3]=ceList[i][3];
3075            re[4]=ceList[i][4];
3076          }
3077          else
3078          {
3079//--- otherwise ignore
3080            i++;
3081            continue;
3082          }
3083        }
3084        else
3085        {
3086          re[1]=intersect(re[1],ceList[i][1]);
3087        }
3088     }
3089   }
3090//--------------------------------------------------------------------------
3091// Perform last checks and return the result
3092//--------------------------------------------------------------------------
3093   if(size(re)!=4)
3094   {
3095//--- oops: already resolved in all open sets
3096     re[1]=BO[2];
3097     re[2]=-1;
3098     re[3]=0;
3099     re[4]=intvec(0);
3100   }
3101   return(re);
3102}
3103//////////////////////////////////////////////////////////////////////////////
3104static
3105proc SpecialCoeff(list BO,int b,poly f)
3106{
3107//----------------------------------------------------------------------------
3108// Coeff with given hypersurface -- no checks of the hypersurface performed
3109//----------------------------------------------------------------------------
3110   int i,ch;
3111   int e=int(factorial(b));
3112   ideal C;
3113   list L=DeltaList(BO);
3114   int d=size(L);
3115//--- set up ideal
3116   for(i=0;i<b;i++)
3117   {
3118      C=C+L[i+1]^(e/(b-i));
3119   }
3120//--- move to hypersurface V(Z)
3121   ideal Z=f;
3122   C=C,Z;
3123   BO[1]=BO[1]+Z;
3124   BO[2]=C;
3125   for(i=1;i<=size(BO[4]);i++)
3126   {
3127      BO[6][i]=0;             // reset intersection indicator
3128      BO[4][i]=BO[4][i]+Z;    // intersect the E_i
3129      BO[2]=sat(BO[2],BO[4][i]+BO[1])[1];
3130                              // "strict transform" of J w.r.t E, not "total"
3131   }
3132   return(BO);
3133}
3134
3135//////////////////////////////////////////////////////////////////////////////
3136static
3137proc DropCoeff(list BO)
3138"Internal procedure - no help and no example available
3139"
3140{
3141//--- Initialization
3142  int i,j;
3143  list pr=minAssGTZ(BO[2]);
3144  ideal I=BO[2];
3145  ideal Itemp;
3146  ideal Idropped=1;
3147//--- Tests
3148  for(i=1;i<=size(pr);i++)
3149  {
3150     if(i>size(pr))
3151     {
3152//--- the continue statement does not test the loop condition *sigh*
3153        break;
3154     }
3155     if(deg(std(slocus(pr[i]))[1])!=0)
3156     {
3157//--- this component is singular ===> we still need it
3158        i++;
3159        continue;
3160     }
3161     Itemp=sat(I,pr[i])[1];
3162     if(deg(std(Itemp+pr[i])[1])!=0)
3163     {
3164//--- this component is not disjoint from the other ones ===> we still need it
3165        i++;
3166        continue;
3167     }
3168     if(!transversalT(pr[i],BO[4]))
3169     {
3170//--- this component does not meet one of the remaining E_i transversally
3171//--- ===> we still need it
3172        i++;
3173        continue;
3174     }
3175     if(!normalCross(BO[4],pr[i]))
3176     {
3177//--- this component is not normal crossing with the remaining E_i
3178//--- ===> we still need it
3179        i++;
3180        continue;
3181     }
3182     if(defined(EE)){kill EE;}
3183     list EE;
3184     for(j=1;j<=size(BO[4]);j++)
3185     {
3186        EE[j]=BO[4][j]+pr[i];
3187     }
3188     if(!normalCross(EE))
3189     {
3190//--- we do not have a normal crossing situation for this component after all
3191//--- ===> we still need it
3192        i++;
3193        continue;
3194     }
3195     Idropped=intersect(Idropped,pr[i]);
3196     I=Itemp;
3197  }
3198  return(Idropped);
3199}
3200
3201//////////////////////////////////////////////////////////////////////////////
3202static
3203proc DropRedundant(list BO,list E)
3204"Internal procedure - no help and no example available
3205"
3206{
3207//---------------------------------------------------------------------------
3208// Initialization and sanity checks
3209//---------------------------------------------------------------------------
3210  int ii,jj,kkdiff,nonnormal,ok;
3211  ideal testid,dummy;
3212  ideal center;
3213  intvec transverse,dontdrop,zerovec;
3214  transverse[size(BO[4])]=0;
3215  dontdrop[size(E[4])]=0;
3216  zerovec[size(E[4])]=0;
3217  ideal J=BO[2];
3218  int dimJ=dim(std(BO[2]));
3219  list templist;
3220  if(size(E)<5)
3221  {
3222//--- should not occur
3223    return(E);
3224  }
3225  for(ii=1;ii<=BO[7][1];ii++)
3226  {
3227     if(BO[6][ii]==2)
3228     {
3229       kkdiff++;
3230     }
3231  }
3232  int expDim=dimJ-E[2]+kkdiff;
3233  if(size(E)==6)
3234  {
3235    nonnormal=E[6];
3236  }
3237//---------------------------------------------------------------------------
3238// if dimJ were smaller than E[2], we would not have more than 3 entries in
3239//    in the list E
3240// if dimJ is also at least E[3] and nonnormal is 0, we only need to test that
3241// * the intersection is of the expected dimension
3242// * the intersections of the BO[4][i] and J are normal crossing
3243// * the elements of E^+ have no influence (is done below)
3244//---------------------------------------------------------------------------
3245  if((E[3]<=dimJ)&&(!nonnormal))
3246  {
3247    ideal bla=E[1]+BO[2]+BO[1];
3248    bla=radical(bla);
3249    bla=mstd(bla)[2];
3250
3251    if(dim(std(slocusE(bla)))<0)
3252    {
3253      if(transversalT(J,BO[4]))
3254      {
3255        ok=1;
3256        if(E[2]==E[3])
3257        {
3258//--- no further intersection with elements from E^+
3259          for(ii=1;ii<=size(E[4]);ii++)
3260          {
3261            if(dim_slocus(BO[2]+E[4][ii])!=-1)
3262            {
3263              dontdrop[ii]=1;
3264            }
3265          }
3266          if(dontdrop==zerovec)
3267          {
3268            list relist;
3269            relist[1]=std(J);
3270            return(relist);
3271          }
3272        }
3273      }
3274    }
3275  }
3276//---------------------------------------------------------------------------
3277// now check whether the E_i actually occurring in the intersections meet
3278// J transversally (one by one) and mark those elements of E[4] where it is
3279// not the case
3280//---------------------------------------------------------------------------
3281 if(!ok)
3282 {
3283     for(ii=1;ii<=size(E[5]);ii++)
3284     {
3285//--- test the ii-th tuple of E[4] resp. its indices E[5]
3286       for(jj=1;jj<=size(E[5][ii]);jj++)
3287       {
3288//--- if E[5][ii][jj]==1, E_jj is involved in E[4][ii]
3289        if(E[5][ii][jj]==1)
3290         {
3291//--- transversality not yet determined
3292           if(transverse[jj]==0)
3293           {
3294             templist[1]=BO[4][jj];
3295             if(transversalT(BO[2],templist))
3296             {
3297               transverse[jj]=1;
3298             }
3299             else
3300             {
3301               transverse[jj]=-1;
3302               dontdrop[ii]=1;
3303             }
3304           }
3305           else
3306           {
3307//--- already computed transversality
3308             if(transverse[jj]<0)
3309             {
3310               dontdrop[ii]=1;
3311             }
3312           }
3313         }
3314       }
3315     }
3316   }
3317//---------------------------------------------------------------------------
3318// if one of the non-marked tuples from E^- in E[4] has an intersection
3319// of the expected dimension and does not meet any E_i from E^+
3320// - except the ones which are met trivially - , it should be
3321// dropped from the list.
3322// it can also be dropped if an intersection occurs and normal crossing has
3323// been checked.
3324//---------------------------------------------------------------------------
3325  for(ii=1;ii<=size(E[4]);ii++)
3326  {
3327//--- if E[4][ii] does not have transversal intersections, we cannot drop it
3328    if(dontdrop[ii]==1)
3329    {
3330      ii++;
3331      continue;
3332    }
3333//--- testing ii-th tuple from E[4]
3334    testid=BO[1]+BO[2]+E[4][ii];
3335    if(dim(std(testid))!=expDim)
3336    {
3337//--- not expected dimension
3338      dontdrop[ii]=1;
3339      ii++;
3340      continue;
3341    }
3342    testid=mstd(testid)[2];
3343
3344    if(dim(std(slocusE(testid)))>=0)
3345    {
3346//--- not smooth, i.e. more than one component which intersect
3347      dontdrop[ii]=1;
3348      ii++;
3349      continue;
3350    }
3351//--- if E^+ is empty, we are done; otherwise check intersections with E^+
3352    if(BO[7][1]!=-1)
3353    {
3354      if(defined(pluslist)){kill pluslist;}
3355      list pluslist;
3356      for(jj=BO[7][1]+1;jj<=size(BO[4]);jj++)
3357      {
3358        dummy=BO[4][jj]+testid;
3359        dummy=std(dummy);
3360        if(expDim==dim(dummy))
3361        {
3362//--- intersection has wrong dimension
3363          dontdrop[ii]=1;
3364          break;
3365        }
3366        pluslist[jj-BO[7][1]]=BO[4][jj]+testid;
3367      }
3368      if(dontdrop[ii]==1)
3369      {
3370        ii++;
3371        continue;
3372      }
3373      if(!normalCross(pluslist))
3374      {
3375//--- unfortunately, it is not normal crossing
3376        dontdrop[ii]=1;
3377      }
3378    }
3379  }
3380//---------------------------------------------------------------------------
3381// The returned list should look like the truncated output of inters_E
3382//---------------------------------------------------------------------------
3383  list retlist;
3384  for(ii=1;ii<=size(E[4]);ii++)
3385  {
3386    if(dontdrop[ii]==1)
3387    {
3388      if(size(center)>0)
3389      {
3390        center=intersect(center,E[4][ii]);
3391      }
3392      else
3393      {
3394        center=E[4][ii];
3395      }
3396    }
3397  }
3398  retlist[1]=center;
3399  retlist[2]=E[2];
3400  retlist[3]=E[3];
3401  return(retlist);
3402}
3403//////////////////////////////////////////////////////////////////////////////
3404static
3405proc transversalT(ideal J, list E,list #)
3406"Internal procedure - no help and no example available
3407"
3408{
3409//----------------------------------------------------------------------------
3410// check whether J and each element of the list E meet transversally
3411//----------------------------------------------------------------------------
3412   def R=basering;
3413   if(size(#)>0)
3414   {
3415     ideal pp=#[1];
3416   }
3417   int i;
3418   ideal T,M;
3419   ideal Jstd=std(J);
3420   ideal Tstd;
3421   int d=nvars(basering)-dim(Jstd)+1;   // d=n-dim(V(J) \cap hypersurface)
3422   for(i=1;i<=size(E);i++)
3423   {
3424      if(size(reduce(E[i],Jstd))==0)
3425      {
3426//--- V(J) is contained in E[i]
3427        return(0);
3428      }
3429      T=J,E[i];
3430      Tstd=std(T);
3431      d=nvars(basering)-dim(Tstd);
3432      if(deg(Tstd[1])!=0)
3433      {
3434//--- intersection is non-empty
3435//!!! abgeklemmt, da es doch in der Praxis vorkommt und korrekt sein kann!!!
3436//!!! wenn ueberhaupt dann -1 zurueckgeben!!!
3437//         if((d>=4)&&(size(T)>=10)){return(0);}
3438         M=minor(jacob(T),d,Tstd)+T;
3439         M=std(M);
3440         if(deg(M[1])>0)
3441         {
3442//--- intersection is not transversal
3443           if(size(#)==0)
3444           {
3445              return(0);
3446           }
3447           M=std(radical(M));
3448           if(size(reduce(pp,M))>0){return(0);}
3449         }
3450      }
3451   }
3452//--- passed all tests
3453   return(1);
3454}
3455///////////////////////////////////////////////////////////////////////////////
3456static
3457proc transversalTB(ideal J, list E,ideal V)
3458"Internal procedure - no help and no example available
3459"
3460{
3461//----------------------------------------------------------------------------
3462// check whether J and each element of the list E meet transversally
3463//----------------------------------------------------------------------------
3464   def R=basering;
3465
3466   int i;
3467   ideal T,M;
3468   ideal Jstd=std(J);
3469   ideal Tstd;
3470   int d=nvars(basering)-dim(Jstd)+1;   // d=n-dim(V(J) \cap hypersurface)
3471   for(i=1;i<=size(E);i++)
3472   {
3473      if(size(reduce(E[i],Jstd))==0)
3474      {
3475//--- V(J) is contained in E[i]
3476        return(0);
3477      }
3478      T=J,E[i];
3479      Tstd=std(T);
3480      d=nvars(basering)-dim(Tstd);
3481      if(deg(Tstd[1])!=0)
3482      {
3483//--- intersection is non-empty
3484         if((d>=4)&&(size(T)>=10)){return(0);}
3485         M=minor(jacob(T),d,Tstd)+T;
3486         M=std(M+V);
3487         if(deg(M[1])>0)
3488         {
3489            return(0);
3490         }
3491      }
3492   }
3493//--- passed all tests
3494   return(1);
3495}
3496///////////////////////////////////////////////////////////////////////////////
3497static
3498proc powerI(ideal I,int n,int m)
3499{
3500//--- compute (n!/m)-th power of I, more efficient variant
3501   int i;
3502   int mon=1;
3503   for(i=1;i<=size(I);i++)
3504   {
3505     if(size(I[i])>1){mon=0;break;}
3506   }
3507   if(mon)
3508   {
3509      if(size(reduce(I,std(radical(I[1]))))<size(I)-1){mon=0;}
3510   }
3511   if((mon)&&(size(I)>3))
3512   {
3513      int e=int(factorial(n))/m;
3514      ideal J=1;
3515      poly p=I[1];
3516      I=I[2..size(I)];
3517      ideal K=p^e;
3518      for(i=1;i<=e;i++)
3519      {
3520         J=interred(J*I);
3521         K=K,(p^(e-i))*J;
3522      }
3523      return(K);
3524   }
3525   for(i=n;i>1;i--)
3526   {
3527      if(i!=m)
3528      {
3529         I=I^i;
3530      }
3531   }
3532   return(I);
3533}
3534
3535///////////////////////////////////////////////////////////////////////////////
3536static
3537proc Coeff(list BO, int b, list #)
3538"USAGE:  Coeff (BO);
3539@*       BO = basic object, a list: ideal W,
3540@*                                  ideal J,
3541@*                                  intvec b (already truncated for Coeff),
3542@*                                  list Ex  (already truncated for Coeff),
3543@*                                  ideal ab,
3544@*                                  intvec v,
3545@*                                  intvec w (already truncated for Coeff),
3546@*                                  matrix M
3547@*       b  = integer indication bmax(BO)
3548ASSUME:  R  = basering, a polynomial ring, W an ideal of R,
3549@*       J  = ideal containing W
3550COMPUTE: Coeff-Ideal of BO as defined in [Bravo,Encinas,Villamayor]
3551RETURN:  basic object of the Coeff-Ideal
3552EXAMPLE: example Coeff;    shows an example
3553"
3554{
3555//!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3556//!!! TASK: lower dimension by more than one in a single step if possible !!!
3557//!!!       (improve bookkeeping of invariants in Coeff and Center)       !!!
3558//!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3559//---------------------------------------------------------------------------
3560// Initialization  and sanity checks
3561//---------------------------------------------------------------------------
3562   int i,k,dummy,errtype;
3563   int ma=size(BO[4]);
3564   intvec merk;
3565   if(!defined(debugCoeff))
3566   {
3567     int debugCoeff;
3568   }
3569   ideal C;
3570   list L;
3571   if(size(#)!=0)
3572   {
3573      if(typeof(#[1])=="ideal")
3574      {
3575        L=#;
3576      }
3577      else
3578      {
3579        ma=#[1];
3580        L=DeltaList(BO);
3581      }
3582   }
3583   else
3584   {
3585      L=DeltaList(BO);
3586   }
3587
3588   if(debugCoeff)
3589   {
3590     "----> In Coeff: result of DeltaList:";
3591     L;
3592   }
3593   int d=size(L);                   // bmax of BO
3594   if((debugCoeff)&&(d!=b))
3595   {
3596      "!!!!!! Length of DeltaList does not equal second argument !!!!!!";
3597      "!!!!!! BO might not have been ord ~ 1 or wrong b          !!!!!!";
3598   }
3599   if(b>=6){return(0);}              // b is too big
3600   int e=int(factorial(b));          // b of Coeff-Ideal
3601   if(e==0)
3602   {
3603     ERROR( "// integer size too small for forming b! .");
3604   }
3605   if(b==0)
3606   {
3607     ERROR( "// second argument to Coeff should never be zero."  );
3608   }
3609//----------------------------------------------------------------------------
3610// Form the Coeff-Ideal
3611// Step 1: choose hypersurface
3612// Step 2: sum over correct powers of Delta^i(BO[2])
3613// Step 3: do the intersection
3614//----------------------------------------------------------------------------
3615//--- Step 1
3616   ideal Z;
3617   poly p;
3618   for(i=1;i<=ncols(L[d]);i++)
3619   {
3620//--- Look for smooth hypersurface in generators of Delta^(bmax-1)(BO[2])
3621     dummy=goodChoice(BO,L[d][i]);
3622     if(!dummy)
3623     {
3624       Z= L[d][i];
3625       break;
3626     }
3627     else
3628     {
3629       if(dummy>1)
3630       {
3631          merk[size(merk)+1]=i;
3632       }
3633       if(dummy>errtype)
3634       {
3635         errtype=dummy;
3636       }
3637     }
3638   }
3639   if(size(Z)==0)
3640   {
3641//--- no suitable element in generators of Delta^(bmax-1)(BO[2])
3642//--- try random linear combination
3643      for(k=1;k<=10;k++)
3644      {
3645         for(i=2;i<=size(merk);i++)
3646         {
3647            p=p+random(-100,100)*L[d][merk[i]];
3648         }
3649         dummy=goodChoice(BO,p);
3650         if(!dummy)
3651         {
3652            Z=p;
3653            break;
3654         }
3655         else
3656         {
3657            p=0;
3658         }
3659      }
3660      if(dummy)
3661      {
3662        for(i=1;i<=size(L[d]);i++)
3663        {
3664           p=p+random(-100,100)*L[d][i];
3665        }
3666        dummy=goodChoice(BO,p);
3667        if(!dummy)
3668        {
3669//--- found a suitable one
3670           Z=p;
3671        }
3672      }
3673      if(dummy)
3674      {
3675//--- did not find a suitable random linear combination either
3676         if(dummy>errtype)
3677         {
3678           errtype=dummy;
3679         }
3680         list retlist=errtype,L[d];
3681         return(retlist);
3682      }
3683   }
3684   if(debugCoeff)
3685   {
3686     "----> In Coeff: Chosen hypersurface";
3687     Z;
3688   }
3689//--- Step 2
3690   C=Z;
3691   for(i=0;i<b;i++)
3692   {
3693      C=C,powerI(simplify(reduce(L[i+1],std(Z)),2),b,b-i);
3694   }
3695   C=interred(C);
3696
3697   if(debugCoeff)
3698   {
3699     "----> In Coeff: J before saturation";
3700     C;
3701   }
3702
3703//--- Step 3
3704   BO[1]=BO[1]+Z;
3705   BO[2]=C;
3706   for(i=1;i<=size(BO[4]);i++)
3707   {
3708      BO[6][i]=0;             // reset intersection indicator
3709      BO[4][i]=BO[4][i]+Z;    // intersect the E_i
3710      if(i<=ma)
3711      {
3712        BO[2]=sat(BO[2],BO[4][i]+BO[1])[1];
3713                       // "strict transform" of J w.r.t E, not "total"
3714      }
3715   }
3716   if(debugCoeff)
3717   {
3718     "----> In Coeff:";
3719     " J after saturation:";
3720     BO[2];
3721   }
3722   return(BO);
3723}
3724example
3725{"EXAMPLE:";
3726   echo = 2;
3727   ring R=0,(x,y,z),dp;
3728
3729   ideal W;
3730   ideal J=z^2+x^2*y^2;
3731   intvec b=0;
3732   list E;
3733   ideal abb=maxideal(1);
3734   intvec v;
3735   intvec w=-1;
3736   matrix M;
3737
3738   list BO=W,J,b,E,abb,v,w,M;
3739
3740   Coeff(BO,2);
3741}
3742//////////////////////////////////////////////////////////////////////////////
3743static
3744proc goodChoice(list BO, poly p)
3745"Internal procedure - no help and no example available
3746"
3747{
3748//---------------------------------------------------------------------------
3749// test whether new W is smooth
3750//---------------------------------------------------------------------------
3751   ideal W=BO[1]+ideal(p);
3752   if(size(reduce(p,std(BO[1])))==0)
3753   {
3754//--- p is already in BO[1], i.e. does not define a hypersurface in W
3755     return(1);
3756   }
3757   if(dim(std(slocusE(W)))>=0)
3758//   if(dim(timeStd(slocusE(W),20))>=0)
3759   {
3760//--- new W would not be smooth
3761     return(1);
3762   }
3763   if(size(BO[4])==0)
3764   {
3765//--- E is empty, no further tests necessary
3766     return(0);
3767   }
3768//--------------------------------------------------------------------------
3769// test whether the hypersurface meets the E_i transversally
3770//--------------------------------------------------------------------------
3771   list E=BO[4];
3772   int i,d;
3773   ideal T=W;
3774   ideal Tstd=std(T);
3775   d=nvars(basering)-dim(Tstd)+1;
3776   ideal M;
3777   for(i=1;i<=size(E);i++)
3778   {
3779      T=W,E[i];
3780      M=minor(jacob(T),d,Tstd)+T;
3781      M=std(M);
3782      if(deg(M[1])>0)
3783      {
3784//--- intersection not transversal
3785        return(2);
3786      }
3787   }
3788//--------------------------------------------------------------------------
3789// test whether the new E_i have normal crossings
3790//--------------------------------------------------------------------------
3791   for(i=1;i<=size(E);i++)
3792   {
3793      E[i]=E[i],p;
3794   }
3795   if(normalCross(E))
3796   {
3797     return(0);
3798   }
3799   else
3800   {
3801     return(2);
3802   }
3803}
3804//////////////////////////////////////////////////////////////////////////////
3805
3806proc presentTree(list L)
3807"USAGE:  presentTree(L);
3808         L=list, output of resolve
3809RETURN:  nothing, only pretty printing of the output data of resolve()
3810EXAMPLE: none
3811"
3812{
3813  def r=basering;
3814  int i,j,k;
3815  if(size(L[2])==1)
3816  {
3817     "The object was already resolved or the list L does not";
3818     "have required input format. There is just one chart in";
3819     "the tree.";
3820     return();
3821  }
3822  for(i=1;i<=size(L[1]);i++)
3823  {
3824    "                        ";
3825    "/////////////////////////// Final Chart",i,"/////////////////////////";
3826    def s=L[1][i];
3827    setring s;
3828    "======================== History of this chart ======================";
3829    for(j=2;j<=ncols(path);j++)
3830    {
3831      "                  ";
3832      "Blow Up",j-1,":";
3833      "     Center determined in L[2]["+string(path[1,j])+"],";
3834      "     Passing to chart ",path[2,j]," in resulting blow up.";
3835    }
3836    "                 ";
3837    "======================== Data of this chart ========================";
3838    showBO(BO);
3839    setring r;
3840    kill s;
3841    pause();
3842  }
3843  "////////////////////////////////////////////////////////////////////";
3844  "For identification of exceptional divisors please use the tools";
3845  "provided by reszeta.lib, e.g. collectDiv.";
3846  "For viewing an illustration of the tree of charts please use the";
3847  "procedure ResTree from resgraph.lib.";
3848  "////////////////////////////////////////////////////////////////////";
3849  return();
3850}
3851//////////////////////////////////////////////////////////////////////////////
3852
3853proc showBO(list BO)
3854"USAGE:  showBO(BO);
3855@*        BO=basic object, a list: ideal W,
3856@*                                  ideal J,
3857@*                                  intvec b (already truncated for Coeff),
3858@*                                  list Ex  (already truncated for Coeff),
3859@*                                  ideal ab,
3860@*                                  intvec v,
3861@*                                  intvec w (already truncated for Coeff),
3862@*                                  matrix M
3863RETURN:   nothing, only pretty printing
3864EXAMPLE:  none
3865"
3866{
3867  "                       ";
3868  "==== Ambient Space: ";BO[1];"      ";
3869  "==== Ideal of Variety: ";BO[2];"      ";
3870  int i;
3871  list M;
3872  for(i=1;i<=size(BO[4]);i++)
3873  {
3874    M[i]=ideal(BO[4][i]);
3875  }
3876  "==== Exceptional Divisors: ";print(M);"   ";
3877  "==== Images of variables of original ring:";BO[5];"   ";
3878}
3879//////////////////////////////////////////////////////////////////////////////
3880static
3881proc max(int i,int j)
3882"Internal procedure - no help and no example available
3883"
3884{
3885//--- why is there no proc for max in general.lib?
3886  if(i>j){return(i);}
3887  return(j);
3888}
3889//////////////////////////////////////////////////////////////////////////////
3890static
3891proc min(int i,int j)
3892"Internal procedure - no help and no example available
3893"
3894{
3895//--- why is there no proc for max in general.lib?
3896  if(i<j){return(i);}
3897  return(j);
3898}
3899//////////////////////////////////////////////////////////////////////////////
3900////////////////////////    main procedure    ////////////////////////////////
3901//////////////////////////////////////////////////////////////////////////////
3902proc resolve(ideal J, list #)
3903"USAGE:  resolve (J); or resolve (J,i[,k]);
3904@*       J ideal
3905@*       i,k int
3906COMPUTE: a resolution of J,
3907@*       if i > 0 debugging is turned on according to the following switches:
3908@*       j1: value 0 or 1; turn off or on correctness checks in all steps
3909@*       j2: value 0 or 2; turn off or on debugCenter
3910@*       j3: value 0 or 4; turn off or on debugBlowUp
3911@*       j4: value 0 or 8; turn off or on debugCoeff
3912@*       j5: value 0 or 16:turn off or on debugging of Intersection with E^-
3913@*       j6: value 0 or 32:turn off or on stop after pass throught the loop
3914@*       i=j1+j2+j3+j4+j5+j6
3915RETURN:  a list l of 2 lists of rings
3916         l[1][i] is a ring containing a basic object BO, the result of the
3917         resolution.
3918         l[2] contains all rings which occured during the resolution process
3919NOTE:    result may be viewed in a human readable form using presentTree()
3920EXAMPLE: example resolve;  shows an example
3921"
3922{
3923//----------------------------------------------------------------------------
3924// Initialization and sanity checks
3925//----------------------------------------------------------------------------
3926   def R=basering;
3927   list allRings;
3928   allRings[1]=R;
3929   list endRings;
3930   module path=[0,-1];
3931   ideal W;
3932   list E;
3933   ideal abb=maxideal(1);
3934   intvec v;
3935   intvec bvec;
3936   intvec w=-1;
3937   matrix intE;
3938   int extra,bm;
3939   if(defined(BO)){kill BO;}
3940   if(defined(cent)){kill cent;}
3941
3942   ideal Jrad=equiRadical(J);
3943   if(size(reduce(Jrad,std(J)))!=0)
3944   {
3945      "WARNING! The input is not reduced or not equidimensional!";
3946      "We will continue with the reduced top-dimensional part of input";
3947      J=Jrad;
3948   }
3949
3950   int i,j,debu,loca,locaT,ftemp,debugResolve,smooth;
3951//--- switches for local and for debugging may occur in any order
3952   i=size(#);
3953   extra=3;
3954   for(j=1;j<=i;j++)
3955   {
3956     if(typeof(#[j])=="int")
3957     {
3958       debugResolve=#[j];
3959//--- debu: debug switch for resolve, smallest bit in debugResolve
3960       debu=debugResolve mod 2;
3961     }
3962     else
3963     {
3964        if(#[j]=="M")
3965        {
3966           bm=1;
3967           ERROR("Not implemented yet");
3968        }
3969        if(#[j]=="E"){extra=0;}
3970        if(#[j]=="A"){extra=2;}
3971        if(#[j]=="K"){extra=3;}
3972        if(#[j]=="L"){loca=1;}
3973     }
3974   }
3975   if(loca)
3976   {
3977      list qs=minAssGTZ(J);
3978      ideal K=ideal(1);
3979      for(j=1;j<=size(qs);j++)
3980      {
3981         if(size(reduce(qs[j],std(maxideal(1))))==0)
3982         {
3983            K=intersect(K,qs[j]);
3984         }
3985      }
3986      J=K;
3987      list qr=minAssGTZ(slocus(J));
3988      K=ideal(1);
3989      for(j=1;j<=size(qr);j++)
3990      {
3991         if(size(reduce(qr[j],std(maxideal(1))))!=0)
3992         {
3993            K=intersect(K,qr[j]);
3994            smooth++;
3995         }
3996         else
3997         {
3998            if(dim(std(qr[j]))>0){loca=0;}
3999//---- test for isolated singularity at 0
4000         }
4001      }
4002      K=std(K);
4003//---- if deg(K[1])==0 the point 0 is on all components of the singular
4004//---- locus and we can work globally
4005      if(smooth==size(qr)){smooth=-1;}
4006//---- the point 0 is not on the singular locus
4007      if((deg(K[1])>0)&&(smooth>=0)&&(!loca))
4008      {
4009         locaT=1;
4010         poly @p;
4011         for(j=1;j<=size(K);j++)
4012         {
4013            if(jet(K[j],0)!=0)
4014            {
4015               @p=K[j];
4016               break;
4017            }
4018         }
4019         export(@p);
4020      }
4021      if((loca)&&(!smooth)){loca=0;}
4022//---- the case that 0 is isolated singularity and the only singular point
4023   }
4024   export(locaT);
4025//---In case of option "L" the following holds
4026//---loca=0 and locaT=0  we perform the global case
4027//---loca !=0: 0 is isolated singular point, but there are other singularities
4028//---locaT!=0: O is singular point, but not isolated, and there is a componente//---          of the singular locus not containing 0
4029
4030//--- if necessary, set the corresponding debugFlags
4031   if(defined(debugResolve))
4032   {
4033//--- 2nd bit from the right
4034     int debugCenter=(debugResolve div 2) mod 2;
4035     export debugCenter;
4036//--- 3rd bit from the right
4037     int debugBlowUp=(debugResolve div 4) mod 2;
4038     export debugBlowUp;
4039//--- 4th bit from the right
4040     int debugCoeff=(debugResolve div 8) mod 2;
4041     export debugCoeff;
4042//--- 5th bit from the right
4043     int debug_Inters_E=(debugResolve div 16) mod 2;
4044     export debug_Inters_E;
4045//--- 6th bit from the right
4046     int praes_stop=(debugResolve div 32) mod 2;
4047   }
4048//--- set the correct attributes to J for speed ups
4049   if( typeof(attrib(J,"isEqui"))!="int" )
4050   {
4051      if(size(J)==1)
4052      {
4053         attrib(J,"isEqui",1);
4054      }
4055      else
4056      {
4057         attrib(J,"isEqui",0);
4058      }
4059   }
4060   if(size(J)==1)
4061   {
4062      attrib(J,"isHy",1);
4063   }
4064   else
4065   {
4066      attrib(J,"isHy",0);
4067   }
4068//--- create the BO
4069   list BO=W,J,bvec,E,abb,v,w,intE;
4070   if(defined(invSat)){kill invSat;}
4071   list invSat=ideal(0),intvec(0);
4072   export(invSat);
4073   if(bm)
4074   {
4075     intmat invmat[2][1]=0,-1;
4076     BO[9]=invmat;
4077   }
4078   else
4079   {
4080     BO[9]=intvec(0);
4081   }
4082   export BO;
4083   list tmpList;
4084   int blo;
4085   int k,Ecount,tmpPtr;
4086   i=0;
4087   if(smooth==-1)
4088   {
4089      endRings[1]=R;
4090      list result=endRings,allRings;
4091      if(debu)
4092      {
4093         "============= result will be tested ==========";
4094         "                                              ";
4095         "the number of charts obtained:",size(endRings);
4096         "=============     result is o.k.    ==========";
4097      }
4098      kill debugCenter,debugBlowUp,debugCoeff,debug_Inters_E;
4099      return(result);
4100   }
4101//-----------------------------------------------------------------------------
4102// While there are rings to be considered, determine center and blow up
4103//-----------------------------------------------------------------------------
4104   while(i<size(allRings))
4105   {
4106      i++;
4107      def S=allRings[i];
4108      setring S;
4109      list pr;
4110      ideal Jstd=std(BO[2]);
4111//-----------------------------------------------------------------------------
4112// Determine Center
4113//-----------------------------------------------------------------------------
4114      if(i==1)
4115      {
4116         list deltaL=DeltaList(BO);
4117         ideal sL=radical(deltaL[size(deltaL)]);
4118         if((deg(std(slocus(sL))[1])==0)&&(size(minAssGTZ(sL))==1))
4119         {
4120            list @ce=sL,intvec(-1),intvec(0),intvec(0);
4121            ideal cent=@ce[1];
4122         }
4123      }
4124//--- before computing a center, check whether we have a stored one
4125      if(size(BO)>9)
4126      {
4127         while(size(BO[10])>0)
4128         {
4129            list @ce=BO[10][1];
4130//--- check of the center
4131           // @ce=correctC(BO,@ce,bm);
4132//--- use stored center
4133            BO[10]=delete(BO[10],1);
4134            if(size(@ce[1])==0)
4135            {
4136//--- stored center was not ok
4137              continue;
4138            }
4139            tmpPtr=0;
4140            for(Ecount=1;Ecount <= size(@ce[2]); Ecount++)
4141            {
4142              if(@ce[2][Ecount]>-1)
4143              {
4144                tmpPtr=tmpPtr+@ce[2][Ecount];
4145              }
4146              else
4147              {
4148                @ce[2][Ecount]=size(BO[4])-tmpPtr-1;
4149                for(int cnthlp=1;cnthlp<=size(BO[10]);cnthlp++)
4150                {
4151                   BO[10][cnthlp][2][Ecount]=@ce[2][Ecount];
4152                }
4153                kill cnthlp;
4154                break;
4155              }
4156            }
4157            if(Ecount<size(@ce[2]))
4158            {
4159              for(tmpPtr=Ecount+1;tmpPtr<=size(@ce[2]);tmpPtr++)
4160              {
4161                @ce[2][tmpPtr]=0;
4162                for(int cnthlp=1;cnthlp<=size(BO[10]);cnthlp++)
4163                {
4164                   BO[10][cnthlp][2][tmpPtr]=@ce[2][tmpPtr];
4165                }
4166                kill cnthlp;
4167              }
4168            }
4169            break;
4170         }
4171         if(defined(@ce))
4172         {
4173           if(size(@ce[1])==0)
4174           {
4175              kill @ce;
4176           }
4177           else
4178           {
4179              ideal cent=@ce[1];
4180           }
4181         }
4182         if(size(BO[10])==0)
4183         {
4184//--- previously had stored centers, all have been used; we need to clean up
4185            BO=delete(BO,10);
4186         }
4187      }
4188      if((loca)&&(i==1))
4189      {
4190//--- local case: initial step is blow-up in origin
4191         if(defined(@ce)){kill @ce;}
4192         if(defined(cent)){kill cent;}
4193         if(size(reduce(slocusE(BO[2]),std(maxideal(1))))==0)
4194         {
4195            list @ce=maxideal(1),intvec(-1),intvec(0),intvec(0);
4196         }
4197         else
4198         {
4199            list @ce=BO[2],intvec(-1),intvec(1),intvec(0);
4200         }
4201         ideal cent=@ce[1];
4202      }
4203      if(((loca)||(locaT))&&(i!=1))
4204      {
4205         int JmeetsE;
4206         for(j=1;j<=size(BO[4]);j++)
4207         {
4208            if(deg(std(BO[2]+BO[4][j])[1])!=0)
4209            {
4210               JmeetsE=1;
4211               break;
4212            }
4213         }
4214         if(!JmeetsE)
4215         {
4216            list @ce=BO[2],intvec(-1),intvec(1),intvec(0);
4217            ideal cent=@ce[1];
4218         }
4219         kill JmeetsE;
4220      }
4221      if((locaT)&&(!defined(@ce)))
4222      {
4223          if(@p!=1)
4224          {
4225             list tr=minAssGTZ(slocusE(BO[2]));
4226             ideal L=ideal(1);
4227             for(j=1;j<=size(tr);j++)
4228             {
4229                if(size(reduce(ideal(@p),std(tr[j])))==0)
4230                {
4231                   L=intersect(L,tr[j]);
4232                }
4233             }
4234             L=std(L);
4235             if(deg(L[1])==0)
4236             {
4237                @p=1;
4238             }
4239             else
4240             {
4241               ideal fac=factorize(@p,1);
4242               if(size(fac)==1)
4243               {
4244                 @p=fac[1];
4245               }
4246               else
4247               {
4248                  for(j=1;j<=size(fac);j++)
4249                  {
4250                     if(reduce(fac[j],L)==0)
4251                     {
4252                        @p=fac[j];
4253                        break;
4254                     }
4255                  }
4256               }
4257             }
4258             kill tr,L;
4259          }
4260          execute("ring R1=("+charstr(S)+"),(@z,"+varstr(S)+"),dp;");
4261          poly p=imap(S,@p);
4262          list BO=imap(S,BO);
4263          list invSat=imap(S,invSat);
4264          export(invSat);
4265          ideal te=std(BO[2]);
4266          BO[1]=BO[1]+ideal(@z*p-1);
4267          BO[2]=BO[2]+ideal(@z*p-1);
4268          for(j=1;j<=size(BO[4]);j++)
4269          {
4270             BO[4][j]=BO[4][j]+ideal(@z*p-1);
4271          }
4272//--- for computation of center: drop components not meeting the Ei
4273          def BO2=BO;
4274          list qs=minAssGTZ(BO2[2]);
4275          ideal K=ideal(1);
4276          for(j=1;j<=size(qs);j++)
4277          {
4278             if(CompMeetsE(qs[j],BO2[4]))
4279             {
4280                K=intersect(K,qs[j]);
4281             }
4282          }
4283          BO2[2]=K;
4284//--- check whether we are done
4285          if(deg(std(BO2[2])[1])==0)
4286          {
4287             list @ce=BO[2],intvec(-1),intvec(1),intvec(0);
4288          }
4289          if(!defined(@ce))
4290          {
4291             if(bm)
4292             {
4293                list @ce=CenterBM(BO2);
4294             }
4295             else
4296             {
4297                list @ce=CenterBO(BO2);
4298             }
4299          }
4300//--- if computation of center returned BO2[2], we are done
4301//--- ==> set @ce to BO[2], because later checks work with BO instead of BO2
4302          if((size(reduce(@ce[1],std(BO2[2])))==0)&&
4303             (size(reduce(BO2[2],std(@ce[1])))==0))
4304          {
4305             @ce[1]=BO[2];
4306          }
4307          if(size(specialReduce(@ce[1],te,p))==0)
4308          {
4309             BO=imap(S,BO);
4310             @ce[1]=BO[2];
4311          }
4312          else
4313          {
4314             //@ce=correctC(BO,@ce,bm);
4315             @ce[1]=eliminate(@ce[1],@z);
4316          }
4317          setring S;
4318          list @ce=imap(R1,@ce);
4319          kill R1;
4320
4321         if((size(reduce(BO[2],std(@ce[1])))==0)
4322             &&(size(reduce(@ce[1],Jstd))==0))
4323         {
4324//--- J and center coincide
4325            pr[1]=@ce[1];
4326            ideal cent=@ce[1];
4327         }
4328         else
4329         {
4330//--- decompose center and use first component
4331            pr=minAssGTZ(@ce[1]);
4332               if(size(reduce(@p,std(pr[1])))==0){"Achtung";~;}
4333               if(deg(std(slocus(pr[1]))[1])>0){"singulaer";~;}
4334            ideal cent=pr[1];
4335         }
4336         if(size(pr)>1)
4337         {
4338//--- store the other components
4339            for(k=2;k<=size(pr);k++)
4340            {
4341               if(size(reduce(@p,std(pr[k])))==0){"Achtung";~;}
4342               if(deg(std(slocus(pr[k]))[1])>0){"singulaer";~;}
4343               if(size(reduce(@p,std(pr[k])))!=0)
4344               {
4345                  tmpList[size(tmpList)+1]=list(pr[k],@ce[2],@ce[3],@ce[4]);
4346               }
4347            }
4348            BO[10]=tmpList;
4349            kill tmpList;
4350            list tmpList;
4351         }
4352      }
4353      if(!defined(@ce))
4354      {
4355//--- no previously determined center, we need to compute one
4356         if(loca)
4357         {
4358//--- local case: center should be inside exceptional locus
4359            ideal Ex=ideal(1);
4360            k=0;
4361            for(j=1;j<=size(BO[4]);j++)
4362            {
4363               if(deg(BO[4][j][1])!=0)
4364               {
4365                 Ex=Ex*BO[4][j];   //----!!!!hier evtl. Durchschnitt???
4366                 k++;
4367               }
4368            }
4369//--- for computation of center: drop components not meeting the Ei
4370            list BOloc=BO;
4371            list qs=minAssGTZ(BOloc[2]);
4372            ideal K=ideal(1);
4373            for(j=1;j<=size(qs);j++)
4374            {
4375              if(CompMeetsE(qs[j],BOloc[4]))
4376              {
4377                 K=intersect(K,qs[j]);
4378              }
4379            }
4380            BOloc[2]=K;
4381//--- check whether we are done
4382            if(deg(std(BOloc[2])[1])==0)
4383            {
4384               list @ce=BO[2],intvec(-1),intvec(1),intvec(0);
4385            }
4386            if(!defined(@ce))
4387            {
4388              if(BO[3][1]!=0)
4389              {
4390                 BOloc[2]=BO[2]+Ex^((BO[3][1] div k)+1);//!!!!Vereinfachen???
4391              }
4392              else
4393              {
4394                 BOloc[2]=BO[2]+Ex^((size(DeltaList(BO)) div k)+1);
4395              }
4396              if(bm)
4397              {
4398                 list @ce=CenterBM(BOloc);
4399              }
4400              else
4401              {
4402                 list @ce=CenterBO(BOloc);
4403              }
4404              if(size(reduce(Ex,std(@ce[1])))!=0)
4405              {
4406                 list tempPr=minAssGTZ(@ce[1]);
4407                 for(k=size(tempPr);k>=1;k--)
4408                 {
4409                    if(size(reduce(Ex,std(tempPr[k])))!=0)
4410                    {
4411                      tempPr=delete(tempPr,k);
4412                    }
4413                 }
4414                 @ce[1]=1;
4415                 for(k=1;k<=size(tempPr);k++)
4416                 {
4417                    @ce[1]=intersect(@ce[1],tempPr[k]);
4418                 }
4419                 if(deg(std(@ce[1])[1])==0)
4420                 {
4421                    @ce[1]=BO[2];
4422                 }
4423              }
4424            }
4425//--- test whether we are done
4426            if(size(reduce(slocusE(BO[2]),std(@ce[1])))!=0)
4427            {
4428               if(transversalT(BO[2],BO[4]))
4429               {
4430                  if(defined(E)){kill E;}
4431                  list E=BO[4];
4432                  for(j=1;j<=size(E);j++){if(deg(E[j][1])>0){E[j]=E[j]+BO[2];}}
4433                  if(normalCross(E))
4434                  {
4435                     @ce[1]=BO[2];
4436                  }
4437                  kill E;
4438               }
4439            }
4440         }
4441         else
4442         {
4443//--- non-local
4444            if(bm)
4445            {
4446               list @ce=CenterBM(BO);
4447            }
4448            else
4449            {
4450               list @ce=CenterBO(BO);
4451            }
4452//--- check of the center
4453            //@ce=correctC(BO,@ce,bm);
4454            if((size(@ce[1])==0)&&(size(@ce[4])<(size(@ce[3])-1)))
4455            {
4456               intvec xxx=@ce[3];
4457               xxx=xxx[1..size(@ce[4])];
4458               @ce[3]=xxx;
4459               xxx=@ce[2];
4460               xxx=xxx[1..size(@ce[4])];
4461               @ce[2]=xxx;
4462               kill xxx;
4463            }
4464         }
4465         if((size(reduce(BO[2],std(@ce[1])))==0)
4466             &&(size(reduce(@ce[1],Jstd))==0))
4467         {
4468//--- J and center coincide
4469            pr[1]=@ce[1];
4470            ideal cent=@ce[1];
4471         }
4472         else
4473         {
4474//--- decompose center and use first component
4475            pr=minAssGTZ(@ce[1]);
4476            ideal cent=pr[1];
4477         }
4478         if(size(pr)>1)
4479         {
4480//--- store the other components
4481            for(k=2;k<=size(pr);k++)
4482            {
4483               tmpList[k-1]=list(pr[k],@ce[2],@ce[3],@ce[4]);
4484            }
4485            BO[10]=tmpList;
4486            kill tmpList;
4487            list tmpList;
4488         }
4489      }
4490//--- do not forget to update BO[7] and BO[3]
4491      export cent;
4492      BO[7]=@ce[2];
4493      BO[3]=@ce[3];
4494      if((loca||locaT)&&(size(@ce)<4)){@ce[4]=0;} //Provisorium !!!
4495      if((size(@ce[4])<size(@ce[2])-1)||(size(@ce[4])<size(@ce[3])-1))
4496      {
4497        if((deg(std(@ce[1])[1])==0)&&(deg(std(BO[2])[1])==0))
4498        {
4499           intvec nullvec;
4500           nullvec[size(@ce[2])-1]=0;
4501           @ce[4]=nullvec;
4502           kill nullvec;
4503        }
4504        else
4505        {
4506           "ERROR:@ce[4] hat falsche Laenge - nicht-trivialer Fall";
4507           ~;
4508        }
4509      }
4510      if((typeof(@ce[4])=="intvec") || (typeof(@ce[4])=="intmat"))
4511      {
4512        BO[9]=@ce[4];
4513      }
4514//---------------------------------------------------------------------------
4515// various checks and debug output
4516//---------------------------------------------------------------------------
4517      if((debu) || (praes_stop))
4518      {
4519//--- Show BO of this step
4520         "++++++++++++++ Overview of Current Chart +++++++++++++++++++++++";
4521         "Current number of final charts:",size(endRings);
4522         "Total number of charts currently in chart-tree:",size(allRings);
4523         "Index of the current chart in chart-tree:",i;
4524         "++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++";
4525         showBO(BO);
4526         "-------------------------- Upcoming Center ---------------------";
4527         interred(cent);
4528         "----------------------------------------------------------------";
4529      }
4530      if(praes_stop)
4531      {
4532         ~;
4533      }
4534      if(debu)
4535      {
4536//--- various checks, see output for comments
4537         if(size(BO[1])>0)
4538         {
4539            if(deg(BO[1][1])==0)
4540            {
4541               "!!!  W is empty  !!!";
4542               path;
4543               setring R;
4544               kill S;
4545               list result=endRings,allRings;
4546               return(result);
4547            }
4548            if(deg(std(slocusE(BO[1]))[1])>0)
4549            {
4550               "!!!  W not smooth  !!!";
4551               path;
4552               setring R;
4553               kill S;
4554               list result=endRings,allRings;
4555               return(result);
4556            }
4557         }
4558         if((!loca)&&(!locaT))
4559         {
4560            if(deg(std(slocusE(cent+BO[1]))[1])>0)
4561            {
4562               "!!!  Center not smooth  !!!";
4563               path;
4564               std(cent+BO[1]);
4565               ~;
4566               setring R;
4567               kill S;
4568               list result=endRings,allRings;
4569               return(result);
4570            }
4571         }
4572         for(j=1;j<=size(BO[4]);j++)
4573         {
4574            if(deg(BO[4][j][1])>0)
4575            {
4576               if(deg(std(slocusE(BO[4][j]+BO[1]))[1])>0)
4577               {
4578                  "!!!  exceptional divisor is not smooth  !!!";
4579                  path;
4580                  setring R;
4581                  kill S;
4582                  list result=endRings,allRings;
4583                  return(result);
4584               }
4585            }
4586         }
4587         if((!loca)&&(!locaT))
4588         {
4589            if((norC(BO,cent))&&(size(reduce(cent,Jstd))!=0))
4590            {
4591               "!!!  this chart is already finished  !!!";
4592               cent=BO[2];
4593               ~;
4594            }
4595         }
4596      }
4597//----------------------------------------------------------------------------
4598// Do the blow up
4599//----------------------------------------------------------------------------
4600//!!!! Change this as soon as there is time!!!
4601//!!!! quick and dirty bug fix for old shortcut which has not yet been killed
4602if((dim(std(cent))==0)&&defined(shortcut)) {kill shortcut;}
4603//!!! end of bugfix
4604      if(size(reduce(cent,Jstd))!=0)
4605      {
4606//--- center does not equal J
4607         tmpList=blowUpBO(BO,cent,extra);
4608         if((debu)&&(!loca)&&(!locaT))
4609         {
4610//--- test it, if debu is set
4611            if(!testBlowUp(BO,cent,tmpList,i,extra))
4612            {
4613               "non-redundant chart has been killed!";
4614               ~;
4615            }
4616         }
4617//--- extend the list of all rings
4618         allRings[size(allRings)+1..size(allRings)+size(tmpList)]=
4619                         tmpList[1..size(tmpList)];
4620         for(j=1;j<=size(tmpList);j++)
4621         {
4622            def Q=allRings[size(allRings)-j+1];
4623            setring Q;
4624            def path=imap(S,path);
4625            path=path,[i,size(tmpList)-j+1];
4626            export path;
4627            setring S;
4628            kill Q;
4629         }
4630         kill tmpList;
4631         list tmpList;
4632      }
4633      else
4634      {
4635//--- center equals J
4636           k=0;
4637           for(j=1;j<=size(BO[6]);j++)
4638           {
4639              if(BO[6][j]!=1)
4640              {
4641//--- there is an E_i which meets J in this chart
4642                k=1;
4643                break;
4644              }
4645           }
4646           if(k)
4647           {
4648//--- chart finished, non-redundant
4649              endRings[size(endRings)+1]=S;
4650           }
4651      }
4652      kill pr;
4653      setring R;
4654      kill S;
4655   }
4656//---------------------------------------------------------------------------
4657// set up the result, test it (if debu is set) and return it
4658//---------------------------------------------------------------------------
4659   list result=endRings,allRings;
4660   if(debu)
4661   {
4662      "============= result will be tested ==========";
4663      "                                              ";
4664      "the number of charts obtained:",size(endRings);
4665      if(locaT){loca=2;}
4666      int tes=testRes(J,endRings,loca);
4667      if(tes)
4668      {
4669         "=============     result is o.k.    ==========";
4670      }
4671      else
4672      {
4673         "============     result is wrong    =========="; ~;
4674      }
4675   }
4676   kill debugCenter,debugBlowUp,debugCoeff,debug_Inters_E;
4677   if(locaT){kill @p;}
4678   kill locaT;
4679   return(result);
4680}
4681example
4682{"EXAMPLE:";
4683   echo = 2;
4684   ring R=0,(x,y,z),dp;
4685   ideal J=x3+y5+yz2+xy4;
4686   list L=resolve(J,0);
4687   def Q=L[1][7];
4688   setring Q;
4689   showBO(BO);
4690}
4691//////////////////////////////////////////////////////////////////////////
4692//static
4693proc CompMeetsE(ideal J, list E)
4694"Internal procedure - no help and no example available
4695"
4696{
4697   int i;
4698   for(i=1;i<=size(E);i++)
4699   {
4700      if(deg(std(E[i])[1])!=0)
4701      {
4702         if(deg(std(J+E[i])[1])!=0)
4703         {
4704            return(1);
4705         }
4706      }
4707   }
4708   return(0);
4709}
4710
4711//========================================================================
4712//--------------  procedures for testing the result ----------------------
4713//                (not yet commented)
4714//========================================================================
4715
4716//////////////////////////////////////////////////////////////////////////
4717static
4718proc testRes(ideal J,list L,int loca)
4719"Internal procedure - no help and no example available
4720"
4721{
4722   int loc;
4723   if(defined(locaT)){loc=locaT;}
4724   if(loc){loca=0;}
4725   def R=basering;
4726   ideal M=maxideal(1);
4727   int i,j,tr;
4728   for(i=1;i<=size(L);i++)
4729   {
4730      def Q=L[i];
4731      setring Q;
4732      ideal J=BO[2];
4733      list E=BO[4];
4734      map phi=R,BO[5];
4735      ideal K=phi(J)+BO[1];
4736      ideal stTK=std(K);
4737
4738      if(loca)
4739      {
4740         ideal M=phi(M)+BO[1];
4741         ideal stTM=std(M);
4742      }
4743      for(j=1;j<=size(E);j++)
4744      {
4745         if(deg(E[j][1])>0)
4746         {
4747            stTK=sat(stTK,E[j])[1];
4748         }
4749         if(loca)
4750         {
4751            stTM=sat(stTM,E[j])[1];
4752         }
4753      }
4754      ideal sL=slocusE(J);
4755      if(loca){sL=sL+stTM;}
4756      ideal sLstd=std(sL);
4757      if(deg(sLstd[1])>0)
4758      {
4759         if(!loc)
4760         {
4761            "J is not smooth";i;
4762            setring R;
4763            return(0);
4764         }
4765         if(size(reduce(@p,std(radical(sLstd))))>0)
4766         {
4767            "J is not smooth";i;
4768            setring R;
4769            return(0);
4770         }
4771      }
4772      if(!((size(reduce(J,std(stTK)))==0)
4773           &&(size(reduce(stTK,std(J)))==0)))
4774      {
4775         "map is wrong";i;
4776         setring R;
4777         return(0);
4778      }
4779      if(loc){tr=transversalT(J,E,@p);}
4780      else{tr=transversalT(J,E);}
4781      if(!tr)
4782      {
4783         "E not transversal with J";i;
4784         setring R;
4785         return(0);
4786      }
4787      if(!normalCross(E))
4788      {
4789         "E not normal crossings";i;
4790         setring R;
4791         return(0);
4792      }
4793      for(j=1;j<=size(E);j++)
4794      {
4795         if(deg(E[j][1])>0){E[j]=E[j]+J;}
4796      }
4797      if(!normalCross(E))
4798      {
4799         "E not normal crossings with J";i;
4800         setring R;
4801         return(0);
4802      }
4803      kill J,E,phi,K,stTK;
4804      if(loca){kill M,stTM;}
4805      setring R;
4806      kill Q;
4807   }
4808   return(1);
4809}
4810//////////////////////////////////////////////////////////////////////////////
4811static
4812proc testBlowUp(list BO,ideal cent,list tmpList, int j, int extra)
4813{
4814   def R=basering;
4815   int n=nvars(basering);
4816   int i;
4817   if((extra!=3)&&(extra!=2))
4818   {
4819      ideal K=BO[1],BO[2],cent;
4820      for(i=1;i<=size(BO[4]);i++)
4821      {
4822        K=K,BO[4][i];
4823      }
4824      list N=findvars(K,0);
4825      //list N=findvars(BO[2],0);
4826      if(size(N[1])<n)
4827      {
4828         string newvar=string(N[1]);
4829         execute("ring R1=("+charstr(R)+"),("+newvar+"),dp;");
4830         list BO=imap(R,BO);
4831         ideal cent=imap(R,cent);
4832         n=nvars(R1);
4833      }
4834      else
4835      {
4836         def R1=basering;
4837      }
4838   }
4839   else
4840   {
4841      def R1=basering;
4842   }
4843
4844   i=0;
4845   ideal T=cent;
4846   ideal TW;
4847   for(i=1;i<=size(tmpList);i++)
4848   {
4849      def Q=tmpList[i];
4850      setring Q;
4851      map phi=R1,lastMap;
4852      ideal TE=radical(slocusE(BO[2]));
4853      setring R1;
4854      TW=preimage(Q,phi,TE);
4855      T=intersect(T,TW);
4856      kill Q;
4857   }
4858   ideal sL=intersect(slocusE(BO[2]),cent);
4859   if(size(reduce(sL,std(radical(T))))>0){setring R;return(0);}
4860   if(size(reduce(T,std(radical(sL))))>0){setring R;return(0);}
4861   setring R;
4862   return(1);
4863}
4864//////////////////////////////////////////////////////////////////////////////
4865static
4866proc normalCross(list E,list #)
4867"Internal procedure - no help and no example available
4868"
4869{
4870   int loc;
4871   if((defined(locaT))&&(defined(@p)))
4872   {
4873      loc=1;
4874      ideal pp=@p;
4875   }
4876   int i,d,j;
4877   int n=nvars(basering);
4878   list E1,E2;
4879   ideal K,M,Estd,cent;
4880   intvec v,w;
4881   if(size(#)>0){cent=#[1];}
4882
4883   for(i=1;i<=size(E);i++)
4884   {
4885      Estd=std(E[i]);
4886      if(deg(Estd[1])>0)
4887      {
4888         E1[size(E1)+1]=Estd;
4889      }
4890   }
4891   E=E1;
4892   for(i=1;i<=size(E);i++)
4893   {
4894      v=i;
4895      E1[i]=list(E[i],v);
4896   }
4897   list ll;
4898   int re=1;
4899   int ok;
4900   while(size(E1)>0)
4901   {
4902      K=E1[1][1];
4903      v=E1[1][2];
4904      attrib(K,"isSB",1);
4905      E1=delete(E1,1);
4906      d=n-dim(K);
4907      M=minor(jacob(K),d)+K;
4908      if(deg(std(M)[1])>0)
4909      {
4910         if(size(#)>0)
4911         {
4912            if(size(reduce(M,std(cent)))>0)
4913            {
4914               ll[size(ll)+1]=std(M);
4915            }
4916            else
4917            {
4918               ok=1;
4919            }
4920         }
4921         if(!loc)
4922         {
4923            re=0;
4924         }
4925         else
4926         {
4927            if(size(reduce(pp,std(radical(M))))>0){re=0;}
4928         }
4929      }
4930      for(i=1;i<=size(E);i++)
4931      {
4932         for(j=1;j<=size(v);j++){if(v[j]==i){break;}}
4933         if(j<=size(v)){if(v[j]==i){i++;continue;}}
4934         Estd=std(K+E[i]);
4935         w=v;
4936         if(deg(Estd[1])==0){i++;continue;}
4937         if(d==n-dim(Estd))
4938         {
4939            if(size(#)>0)
4940            {
4941               if(size(reduce(Estd,std(cent)))>0)
4942               {
4943                  ll[size(ll)+1]=Estd;
4944               }
4945               else
4946               {
4947                  ok=1;
4948               }
4949            }
4950            if(!loc)
4951            {
4952               re=0;
4953            }
4954            else
4955            {
4956               if(size(reduce(pp,std(radical(M))))>0){re=0;}
4957            }
4958         }
4959         w[size(w)+1]=i;
4960         E2[size(E2)+1]=list(Estd,w);
4961      }
4962      if(size(E2)>0)
4963      {
4964         if(size(E1)>0)
4965         {
4966            E1[size(E1)+1..size(E1)+size(E2)]=E2[1..size(E2)];
4967         }
4968         else
4969         {
4970            E1=E2;
4971         }
4972      }
4973      kill E2;
4974      list E2;
4975   }
4976/*
4977   if((!ok)&&(!re)&&(size(#)==1))
4978   {
4979
4980      "the center is wrong";
4981      "it could be one of the following list";
4982      ll;
4983       ~;
4984   }
4985*/
4986   if((!ok)&&(!re)&&(size(#)==2))
4987   {
4988      return(2);   //for Center correction
4989   }
4990   return(re);
4991}
4992//////////////////////////////////////////////////////////////////////////////
4993static
4994proc normalCrossB(ideal J,list E,ideal V)
4995"Internal procedure - no help and no example available
4996"
4997{
4998   int i,d,j;
4999   int n=nvars(basering);
5000   list E1,E2;
5001   ideal K,M,Estd;
5002   intvec v,w;
5003
5004   for(i=1;i<=size(E);i++)
5005   {
5006      Estd=std(E[i]+J);
5007      if(deg(Estd[1])>0)
5008      {
5009         E1[size(E1)+1]=Estd;
5010      }
5011   }
5012   E=E1;
5013   for(i=1;i<=size(E);i++)
5014   {
5015      v=i;
5016      E1[i]=list(E[i],v);
5017   }
5018   list ll;
5019   int re=1;
5020
5021   while((size(E1)>0)&&(re==1))
5022   {
5023      K=E1[1][1];
5024      v=E1[1][2];
5025      attrib(K,"isSB",1);
5026      E1=delete(E1,1);
5027      d=n-dim(K);
5028      M=minor(jacob(K),d)+K;
5029      if(deg(std(M+V)[1])>0)
5030      {
5031         re=0;
5032         break;
5033      }
5034      for(i=1;i<=size(E);i++)
5035      {
5036         for(j=1;j<=size(v);j++){if(v[j]==i){break;}}
5037         if(j<=size(v)){if(v[j]==i){i++;continue;}}
5038         Estd=std(K+E[i]);
5039         w=v;
5040         if(deg(Estd[1])==0){i++;continue;}
5041         if(d==n-dim(Estd))
5042         {
5043            if(deg(std(Estd+V)[1])>0)
5044            {
5045               re=0;
5046               break;
5047            }
5048         }
5049         w[size(w)+1]=i;
5050         E2[size(E2)+1]=list(Estd,w);
5051      }
5052      if(size(E2)>0)
5053      {
5054         if(size(E1)>0)
5055         {
5056            E1[size(E1)+1..size(E1)+size(E2)]=E2[1..size(E2)];
5057         }
5058         else
5059         {
5060            E1=E2;
5061         }
5062      }
5063      kill E2;
5064      list E2;
5065   }
5066   return(re);
5067}
5068//////////////////////////////////////////////////////////////////////////////
5069static
5070proc norC(list BO,ideal cent)
5071"Internal procedure - no help and no example available
5072"
5073{
5074   int j;
5075   list  E=BO[4];
5076   ideal N=BO[2];
5077   if(BO[3][1]>1){return(0);}
5078   if(deg(std(slocusE(BO[2]))[1])>0){return(0);}
5079   if(!transversalT(N,E)){return(0);}
5080   for(j=1;j<=size(E);j++){if(deg(E[j][1])>0){E[j]=E[j]+N;}}
5081   if(!normalCross(E,cent)){return(0);}
5082   return(1);
5083}
5084//////////////////////////////////////////////////////////////////////////////
5085static
5086proc specialReduce(ideal I,ideal J,poly p)
5087{
5088   matrix M;
5089   int i,j;
5090   for(i=1;i<=ncols(I);i++)
5091   {
5092      M=coeffs(I[i],@z);
5093      I[i]=0;
5094      for(j=1;j<=nrows(M);j++)
5095      {
5096         I[i]=I[i]+M[j,1]*p^(nrows(M)-j);
5097      }
5098      I[i]=reduce(I[i],J);
5099   }
5100   return(I);
5101}
Note: See TracBrowser for help on using the repository browser.