source: git/Singular/LIB/hnoether.lib @ b9b906

spielwiese
Last change on this file since b9b906 was b9b906, checked in by Hans Schönemann <hannes@…>, 23 years ago
*hannes: lib format revisited git-svn-id: file:///usr/local/Singular/svn/trunk@5078 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 127.9 KB
Line 
1// last change, ML: 31.08.00
2///////////////////////////////////////////////////////////////////////////////
3// This library is for Singular 1-3-7 or newer
4
5version="$Id: hnoether.lib,v 1.27 2001-01-16 13:48:30 Singular Exp $";
6category="Singularities";
7info="
8LIBRARY:  hnoether.lib   Hamburger-Noether (Puiseux) Development
9AUTHOR:   Martin Lamm,   lamm@mathematik.uni-kl.de
10
11OVERVIEW:
12 A library for computing the Hamburger-Noether resp. Puiseux development
13 of a plane curve singularity following A. Campillo: Algebroid curves
14 in positive characteristic, Lecture Notes in Math. 813, Springer (1980).
15 The library contains also procedures for computing the (topological)
16 numerical invariants of plane curve singularities.
17
18MAIN PROCEDURES:
19 HNdevelop(f);              Hamburger-Noether (H-N) development of f
20 develop(f [,n]);           H-N development of irreducible curves
21 reddevelop(f);             H-N development of reducible curves
22 essdevelop(f);             H-N development of essential branches
23 extdevelop(hne,n);         extension of the H-N development hne of f
24 param(hne [,x]);           a parametrization of f (input=output(develop))
25 displayHNE(hne);           display H-N development as an ideal
26 invariants(hne);           invariants of f, e.g. the characteristic exponents
27 multsequence(hne);         sequence of multiplicities
28 displayInvariants(hne);    display invariants of f
29 intersection(hne1,hne2);   intersection multiplicity of two curves
30 displayMultsequence(hne);  display sequence of multiplicities
31 stripHNE(hne);             reduce amount of memory consumed by hne
32 is_irred(f);               test for irreducibility
33
34AUXILIARY PROCEDURES:
35 puiseux2generators(m,n);   convert Puiseux pairs to generators of semigroup
36 multiplicities(hne);       multiplicities of blowed up curves
37 separateHNE(hne1,hne2);    number of quadratic transf. needed for separation
38 squarefree(f);             a squarefree divisor of the poly f
39 allsquarefree(f,l);        the maximal squarefree divisor of the poly f
40 further_hn_proc();         show further procedures useful for interactive use
41
42KEYWORDS: Hamburger-Noether expansion; Puiseux expansion; curve singularities
43";
44///////////////////////////////////////////////////////////////////////////////
45LIB "primitiv.lib";
46LIB "inout.lib";
47
48///////////////////////////////////////////////////////////////////////////////
49
50proc further_hn_proc()
51"USAGE: further_hn_proc();
52   The library `hnoether.lib' contains some more procedures which are not
53   shown when typing @code{help hnoether.lib}. They may be useful for
54   interactive use (e.g. if you want to do the calculation of a HNE
55   \"by hand\" to see the intermediate results), and they can be enumerated by
56   calling further_hn_proc. Use @code{help <procedure>;} for detailed
57   information about each of them.
58"
59{
60 "
61 The following procedures are also part of the library `hnoether.lib':
62
63 newtonpoly(f);      Newton polygon of polynom f
64 getnm(f);           intersection pts. of Newton polygon with the axes
65 T_Transform(f,Q,N); returns f(y,xy^Q)/y^NQ (f: poly, Q,N: int)
66 T1_Transform(f,d,M); returns f(x,y+d*x^M)  (f: poly,d:number,M:int)
67 T2_Transform(f,d,M,N,ref);   a composition of T1 & T
68 koeff(f,I,J);       gets coefficient of indicated monomial of poly f
69 redleit(f,S,E);     restriction of monomials of f to line (S-E)
70 leit(f,n,m);        special case of redleit (for irred. polynomials)
71 testreducible(f,n,m); tests whether f is reducible
72 charPoly(f,M,N);    characteristic polynomial of f
73 find_in_list(L,p);  find int p in list L
74 get_last_divisor(M,N); last divisor in Euclid's algorithm
75 factorfirst(f,M,N); try to factor f in a trivial way without `factorize'
76 factorlist(L);      factorize a list L of polynomials
77 referencepoly(D);   a polynomial f s.t. D is the Newton diagram of f";
78
79// extrafactor(f,M,N); try to factor charPoly(f,M,N) where 'factorize' cannot
80// (will hopefully become obsolete soon)
81//
82//       static procedures not useful for interactive use:
83// polytest(f);        tests coefficients and exponents of poly f
84// extractHNEs(H,t);   extracts output H of HN to output of reddevelop
85// HN(f,grenze);       recursive subroutine for reddevelop
86// constructHNEs(...); subroutine for HN
87}
88example
89{ echo=2;
90  further_hn_proc();
91}
92///////////////////////////////////////////////////////////////////////////////
93
94proc getnm (poly f)
95"USAGE:   getnm(f); f bivariate polynomial
96RETURN:  intvec(n,m) : (0,n) is the intersection point of the Newton
97         polygon of f with the y-axis, n=-1 if it doesn't exist
98         (m,0) is its intersection point with the x-axis,
99         m=-1 if this point doesn't exist
100ASSUME:  ring has ordering `ls' or `ds'
101EXAMPLE: example getnm; shows an example
102"
103{
104 // assume being called by develop ==> ring ordering is ls (ds would also work)
105 return(ord(subst(f,var(1),0)),ord(subst(f,var(2),0)));
106}
107example
108{ "EXAMPLE:"; echo = 2;
109   ring r = 0,(x,y),ds;
110   poly f = x5+x4y3-y2+y4;
111   getnm(f);
112}
113///////////////////////////////////////////////////////////////////////////////
114
115proc leit (poly f, int n, int m)
116"USAGE:   leit(f,n,m);  poly f, int n,m
117RETURN:  all monomials on the line from (0,n) to (m,0) in the Newton diagram
118EXAMPLE: example leit;  shows an example
119"
120{
121 return(jet(f,m*n,intvec(n,m))-jet(f,m*n-1,intvec(n,m)))
122}
123example
124{ "EXAMPLE:"; echo = 2;
125   ring r = 0,(x,y),ds;
126   poly f = x5+x4y3-y2+y4;
127   leit(f,2,5);
128}
129///////////////////////////////////////////////////////////////////////////////
130proc testreducible (poly f, int n, int m)
131"USAGE:   testreducible(f,n,m);  f poly, n,m int
132RETURN:  1 if there are points in the Newton diagram below the line (0,n)-(m,0)
133         0 else
134EXAMPLE: example testreducible;  shows an example
135"
136{
137 return(size(jet(f,m*n-1,intvec(n,m))) != 0)
138}
139example
140{ "EXAMPLE:"; echo = 2;
141  ring rg=0,(x,y),ls;
142  testreducible(x2+y3-xy4,3,2);
143}
144///////////////////////////////////////////////////////////////////////////////
145proc T_Transform (poly f, int Q, int N)
146"USAGE:   T_Transform(f,Q,N);  f poly, Q,N int
147RETURN:  f(y,xy^Q)/y^NQ   if x,y are the ring variables
148NOTE:    this is intended for irreducible power series f
149EXAMPLE: example T_Transform;  shows an example
150"
151{
152 map T = basering,var(2),var(1)*var(2)^Q;
153 return(T(f)/var(2)^(N*Q));
154}
155example
156{ "EXAMPLE:"; echo = 2;
157  ring exrg=0,(x,y),ls;
158  export exrg;
159  T_Transform(x3+y2-xy3,1,2);
160  kill exrg;
161}
162///////////////////////////////////////////////////////////////////////////////
163proc T1_Transform (poly f, number d, int Q)
164"USAGE:   T1_Transform(f,d,Q);  f poly, d number, Q int
165RETURN:  f(x,y+d*x^Q)   if x,y are the ring variables
166EXAMPLE: example T1_Transform;  shows an example
167"
168{
169 map T1 = basering,var(1),var(2)+d*var(1)^Q;
170 return(T1(f));
171}
172example
173{ "EXAMPLE:"; echo = 2;
174  ring exrg=0,(x,y),ls;
175  export exrg;
176  T1_Transform(y2-2xy+x2+x2y,1,1);
177  kill exrg;
178}
179///////////////////////////////////////////////////////////////////////////////
180
181proc T2_Transform (poly f, number d, int M, int N, poly refpoly)
182"USAGE:   T2_Transform(f,d,M,N,ref); f poly, d number; M,N int; ref poly
183RETURN:  list: poly T2(f,d',M,N), number d' in \{ d, 1/d \}
184ASSUME:  ref has the same Newton polygon as f (but can be simpler)
185         for this you can e.g. use the proc `referencepoly' or simply f again
186COMMENT: T2 is a composition of T_Transform and T1_Transform; the exact
187         definition can be found in  Rybowicz: `Sur le calcul des places ...'
188         or in  Lamm: `Hamburger-Noether-Entwicklung von Kurvensingularitaeten'
189SEE ALSO: T_Transform, T1_Transform, referencepoly
190EXAMPLE: example T2_Transform;  shows an example
191"
192{
193 //---------------------- compute gcd and extgcd of N,M -----------------------
194  int ggt=gcd(M,N);
195  M=M/ggt; N=N/ggt;
196  list ts=extgcd(M,N);
197  int tau,sigma=ts[2],-ts[3];
198  int s,t;
199  poly xp=var(1);
200  poly yp=var(2);
201  poly hilf;
202  if (sigma<0) { tau=-tau; sigma=-sigma;}
203 // es gilt: 0<=tau<=N, 0<=sigma<=M, |N*sigma-M*tau| = 1 = ggT(M,N)
204  if (N*sigma < M*tau) { d = 1/d; }
205 //--------------------------- euklid. Algorithmus ----------------------------
206  int R;
207  int M1,N1=M,N;
208  for ( R=M1%N1; R!=0; ) { M1=N1; N1=R; R=M1%N1;}
209  int Q=M1 / N1;
210  map T1 = basering,xp,yp+d*xp^Q;
211  map Tstar=basering,xp^(N-Q*tau)*yp^tau,xp^(M-sigma*Q)*yp^sigma;
212  if (defined(HNDebugOn)) {
213   "Trafo. T2: x->x^"+string(N-Q*tau)+"*y^"+string(tau)+", y->x^"
214    +string(M-sigma*Q)+"*y^"+string(sigma);
215   "delta =",d,"Q =",Q,"tau,sigma =",tau,sigma;
216  }
217 //------------------- Durchfuehrung der Transformation T2 --------------------
218  f=Tstar(f);
219  refpoly=Tstar(refpoly);
220 //--- dividiere f so lange durch x & y, wie die Div. aufgeht, benutze ein  ---
221 //--- Referenzpolynom mit gleichem Newtonpolynom wie f zur Beschleunigung: ---
222  for (hilf=refpoly/xp; hilf*xp==refpoly; hilf=refpoly/xp) {refpoly=hilf; s++;}
223  for (hilf=refpoly/yp; hilf*yp==refpoly; hilf=refpoly/yp) {refpoly=hilf; t++;}
224  f=f/(xp^s*yp^t);
225  return(list(T1(f),d));
226}
227example
228{ "EXAMPLE:"; echo = 2;
229  ring exrg=0,(x,y),ds;
230  export exrg;
231  poly f=y2-2x2y+x6-x5y+x4y2;
232  T2_Transform(f,1/2,4,1,f);
233  T2_Transform(f,1/2,4,1,referencepoly(newtonpoly(f)));
234  // if  size(referencepoly) << size(f)  the 2nd example would be faster
235  referencepoly(newtonpoly(f));
236  kill exrg;
237}
238///////////////////////////////////////////////////////////////////////////////
239
240proc koeff (poly f, int I, int J)
241"USAGE:   koeff(f,I,J); f bivariate polynomial, I,J integers
242RETURN:  if f = sum(a(i,j)*x^i*y^j), then koeff(f,I,J)= a(I,J) (of type number)
243NOTE:    J must be in the range of the exponents of the 2nd ring variable
244EXAMPLE: example koeff;  shows an example
245"
246{
247  matrix mat = coeffs(coeffs(f,var(2))[J+1,1],var(1));
248  if (size(mat) <= I) { return(0);}
249  else { return(leadcoef(mat[I+1,1]));}
250}
251example
252{ "EXAMPLE:"; echo = 2;
253  ring r=0,(x,y),dp;
254  koeff(x2+2xy+3xy2-x2y-2y3,1,2);
255}
256///////////////////////////////////////////////////////////////////////////////
257
258proc squarefree (poly f)
259"USAGE:  squarefree(f);  f a bivariate polynomial
260RETURN: a squarefree divisor of f.
261        Normally the return value is a greatest squarefree divisor, but there
262        is an exception: factors with a p-th root, p the ring characteristic,
263        are lost.
264SEE ALSO: allsquarefree
265EXAMPLE: example squarefree; shows some examples.
266"
267{
268 //----------------- Wechsel in geeigneten Ring & Variablendefinition ---------
269  def altring = basering;
270  int e;
271  int gcd_ok=1;
272  string mipl="0";
273  if (size(parstr(altring))==1) { mipl=string(minpoly); }
274 //---- test: char = (p^k,a) (-> gcd not implemented) or (p,a) (gcd works) ----
275  if ((char(basering)!=0) and (charstr(basering)!=string(char(basering)))) {
276    string tststr=charstr(basering);
277    tststr=tststr[1..find(tststr,",")-1];           //-> "p^k" bzw. "p"
278    gcd_ok=(tststr==string(char(basering)));
279  }
280  execute("ring rsqrf = ("+charstr(altring)+"),(x,y),dp;");
281  if ((gcd_ok!=0) && (mipl!="0")) { execute("minpoly="+mipl+";"); }
282  poly f=fetch(altring,f);
283  poly dif,g,l;
284  if ((char(basering)==0) and (charstr(basering)!=string(char(basering)))
285      and (mipl!="0")) {
286    gcd_ok=0;                   // since Singular 1.2 gcd no longer implemented
287  }
288  if (gcd_ok!=0) {
289 //--------------------- Berechne f/ggT(f,df/dx,df/dy) ------------------------
290    dif=diff(f,x);
291    if (dif==0) { g=f; }        // zur Beschleunigung
292    else { g=gcd(f,dif); }
293    if (g!=1) {                 // sonst schon sicher, dass f quadratfrei
294     dif=diff(f,y);
295     if (dif!=0) { g=gcd(g,dif); }
296    }
297    if (g!=1) {
298     e=0;
299     if (g==f) { l=1; }         // zur Beschleunigung
300     else {
301       module m=syz(ideal(g,f));
302       if (deg(m[2,1])>0) {
303         "!! The Singular command 'syz' has returned a wrong result !!";
304         l=1;                   // Division f/g muss aufgehen
305       }
306       else { l=m[1,1]; }
307     }
308    }
309    else { e=1; }
310  }
311  else {
312 //------------------- Berechne syz(f,df/dx) oder syz(f,df/dy) ----------------
313 //-- Achtung: Ist f reduzibel, koennen Faktoren mit Ableitung Null verloren --
314 //-- gehen! Ist aber nicht weiter schlimm, weil char (p^k,a) nur im irred.  --
315 //-- Fall vorkommen kann. Wenn f nicht g^p ist, wird auf jeden Fall         --
316 //------------------------ ein Faktor gefunden. ------------------------------
317    dif=diff(f,x);
318    if (dif == 0) {
319     dif=diff(f,y);
320     if (dif==0) { e=2; l=1; } // f is of power divisible by char of basefield
321     else { l=syz(ideal(dif,f))[1,1];  // x^p+y^(p-1) abgedeckt
322            if (subst(f,x,0)==0) { l=l*x; }
323            if (deg(l)==deg(f))  { e=1;}
324            else {e=0;}
325     }
326    }
327    else { l=syz(ideal(dif,f))[1,1];
328           if (subst(f,y,0)==0) { l=l*y; }
329           if (deg(l)==deg(f))  { e=1;}
330           else {e=0;}
331    }
332  }
333 //--------------- Wechsel in alten Ring und Rueckgabe des Ergebnisses --------
334  setring altring;
335  if (e==1) { return(f); }    // zur Beschleunigung
336  else {
337   poly l=fetch(rsqrf,l);
338   return(l);
339  }
340}
341example
342{ "EXAMPLE:"; echo = 2;
343 ring exring=3,(x,y),dp;
344 squarefree(x3+y);
345 squarefree(x3);
346 squarefree(x2);
347 squarefree(xy+x);
348 squarefree((x+y)^3*(x-y)^2); // (x+y)^3 is lost
349 squarefree((x+y)^4*(x-y)^2); // result is (x+y)*(x-y)
350}
351///////////////////////////////////////////////////////////////////////////////
352
353proc allsquarefree (poly f, poly l)
354"USAGE : allsquarefree(f,l);  poly f,l
355        l is the squarefree divisor of f you get by @code{l=squarefree(f);}
356RETURN: the squarefree divisor of f consisting of all irreducible factors of f
357NOTE  : This proc uses factorize to get the missing factors of f not in l and
358        therefore may be slow.
359SEE ALSO: squarefree
360EXAMPLE: example allsquarefree;  shows an example
361"
362{
363 //------------------------ Wechsel in geeigneten Ring ------------------------
364 def altring = basering;
365 string mipl="0";
366 if (size(parstr(altring))==1) { mipl=string(minpoly); }
367 if ((char(basering)!=0) and (charstr(basering)!=string(char(basering)))) {
368   string tststr=charstr(basering);
369   tststr=tststr[1..find(tststr,",")-1];           //-> "p^k" bzw. "p"
370   if (tststr!=string(char(basering))) {
371     " Sorry -- not implemented for this ring (gcd doesn't work)";
372     return(l);
373   }
374 }
375 execute("ring rsqrf = ("+charstr(altring)+"),(x,y),dp;");
376 if (mipl!="0") { execute("minpoly="+mipl+";"); }
377 poly f=fetch(altring,f);
378 poly l=fetch(altring,l);
379 //---------- eliminiere bereits mit squarefree gefundene Faktoren ------------
380 poly g=l;
381 while (deg(g)!=0) {
382   f=syz(ideal(g,f))[1,1];                         // f=f/g;
383   g=gcd(f,l);
384 }                                                 // jetzt f=h^p
385 //--------------- Berechne uebrige Faktoren mit factorize --------------------
386 if (deg(f)>0) {
387  g=1;
388  ideal factf=factorize(f,1);
389  for (int i=1; i<=size(factf); i++) { g=g*factf[i]; }
390  poly testp=squarefree(g);
391  if (deg(testp)<deg(g)) {
392    "!! factorize has not worked correctly !!";
393    if (testp==1) {" We cannot proceed ..."; g=1;}
394    else {" But we could recover some factors..."; g=testp;}
395  }
396  l=l*g;
397 }
398 //--------------- Wechsel in alten Ring und Rueckgabe des Ergebnisses --------
399 setring altring;
400 l=fetch(rsqrf,l);
401 return(l);
402}
403example
404{ "EXAMPLE:"; echo = 2;
405  ring exring=7,(x,y),dp;
406  poly f=(x+y)^7*(x-y)^8;
407  poly l=squarefree(f);
408  l; // x-y found because 7 does not divide 8
409  allsquarefree(f,l); // all factors (x+y)*(x-y) found
410}
411///////////////////////////////////////////////////////////////////////////////
412
413proc is_irred (poly f)
414"USAGE:   is_irred(f); f a squarefree bivariate polynomial
415RETURN:  an integer:
416 @*      is_irred(f) @math{= 1} if f is irreducible as a formal power series
417         over the algebraic closure of its coefficient field (f defines an
418         analytically irreducible curve at zero),
419 @*      is_irred(f) @math{= 0} else.
420NOTE:    @math{f = 0} and units in the ring of formal power series are not
421         considered irreducible.
422KEYWORDS: irreducible power series
423EXAMPLE: example is_irred;  shows an example
424"
425{
426  int pl=printlevel;
427  printlevel=-1;
428  list hnl=develop(f,-1);
429  printlevel=pl;
430  return(hnl[5]);
431}
432example
433{ "EXAMPLE:"; echo = 2;
434  ring exring=0,(x,y),ls;
435  is_irred(x2+y3);
436  is_irred(x2+y2);
437  is_irred(x2+y3+1);
438}
439///////////////////////////////////////////////////////////////////////////////
440
441static proc polytest(poly f)
442"USAGE : polytest(f); f poly in x and y
443RETURN: a monomial of f with |coefficient| > 16001
444          or exponent divisible by 32003, if there is one
445        0 else (in this case computing a squarefree divisor
446                in characteristic 32003 could make sense)
447NOTE:   this procedure is only useful in characteristic zero, because otherwise
448        there is no appropriate ordering of the leading coefficients
449"
450{
451 poly verbrecher=0;
452 intvec leitexp;
453 for (; (f<>0) and (verbrecher==0); f=f-lead(f)) {
454  if ((leadcoef(f)<-16001) or (leadcoef(f)>16001)) {verbrecher=lead(f);}
455  leitexp=leadexp(f);
456  if (( ((leitexp[1] % 32003) == 0)   and (leitexp[1]<>0))
457     or ( ((leitexp[2] % 32003) == 0) and (leitexp[2]<>0)) )
458       {verbrecher=lead(f);}
459 }
460 return(verbrecher);
461}
462
463//////////////////////////////////////////////////////////////////////////////
464
465
466proc develop
467"USAGE:   develop(f [,n]); f polynomial in two variables, n integer
468RETURN:  Hamburger-Noether development of f, in form of a list:
469  @*     [1]: Hamburger-Noether matrix:
470            Each row contains the coefficients of the corresponding line of the
471            Hamburger-Noether expansion (HNE). The end of the line is marked in
472            the matrix as the first ring variable (usually x).
473  @*     [2]: intvec indicating the length of lines of the HNE
474  @*     [3]: int:
475           0  if the 1st ring variable was transversal (with respect to f),
476  @*       1  if the variables were changed at the beginning of the
477              computation,
478           -1 if an error has occurred.
479  @*     [4]: the transformed polynomial of f to make it possible to extend the
480              Hamburger-Noether development a posteriori without having to do
481              all the previous calculation once again (0 if not needed)
482  @*     [5]: int:
483           1  if the curve has exactly one branch (i.e. is irreducible),
484  @*       0  else (i.e. the curve has more than one HNE or f is not valid).
485
486ASSUME:  f irreducible as a power series (for reducible f use
487         @code{reddevelop})
488DISPLAY: The (non zero) elements of the HNE (if not called by another proc).
489
490NOTE: If the optional parameter @math{n} is given, the HN-matrix will have
491      at least @math{n} columns. Otherwise the number of columns will be chosen
492      minimal s.t. the matrix contains all necessary information (i.e. all
493      lines of the HNE but the last (which is in general infinite) have place).
494      If @math{n} is negative, the algorithm is stopped as soon as possible,
495      i.e. the information computed is enough for `@code{invariants}', but the
496      HN-matrix may contain undetermined elements, which are marked with the
497      2nd variable (of the basering).
498      In any case, the optional parameter only affects the calculation of
499      the LAST line of the HNE; @code{develop}(f) gives already all necessary
500      information for the procedure `@code{invariants}'. A negative value of
501      @math{n} will result in a very poor parametrization, but it can make
502      `@code{develop}' faster; a positive value will improve the exactness of
503      the parametrization.
504
505      For time critical computations it is recommended to use
506      \"@code{ring ...,(x,y),ls}\" as basering - it increases the algorithm's
507      speed.
508
509SEE ALSO: reddevelop, extdevelop, displayHNE
510EXAMPLES: example develop; shows an example
511          example param;   shows an example for using the 2nd parameter
512"
513{
514 //--------- Abfangen unzulaessiger Ringe: 1) nur eine Unbestimmte ------------
515 poly f=#[1];
516 if (size(#) > 1) {int maxspalte=#[2];}
517 else             {int maxspalte= 1 ; }
518 if (nvars(basering) < 2) {
519   " Sorry. I need two variables in the ring.";
520   return(list(matrix(maxideal(1)[1]),intvec(0),-1,poly(0),0));}
521 if (nvars(basering) > 2) {
522   " Warning! You have defined too many variables!";
523   " All variables except the first two will be ignored!";}
524
525 string namex=varstr(1); string namey=varstr(2);
526 list return_error=matrix(maxideal(1)[2]),intvec(0),int(-1),poly(0),int(0);
527
528 //------------- 2) mehrere Unbestimmte, weitere unzulaessige Ringe -----------
529 // Wir koennen einheitlichen Rueckgabewert benutzen, aus dem ersichtlich ist,
530 // dass ein Fehler aufgetreten ist: return_error.
531 //----------------------------------------------------------------------------
532
533 if (charstr(basering)=="real") {
534  " The algorithm doesn't work with 'real' as coefficient field.";
535                     // denn : map from characteristic -1 to -1 not implemented
536  return(return_error);
537 }
538 if ((char(basering)!=0) and (charstr(basering)!=string(char(basering)))) {
539 //-- teste, ob char = (p^k,a) (-> a primitiv; erlaubt) oder (p,a[,b,...]) ----
540    string tststr=charstr(basering);
541    tststr=tststr[1..find(tststr,",")-1];           //-> "p^k" bzw. "p"
542    int primit=(tststr==string(char(basering)));
543    if (primit!=0) {
544      " Such extensions of Z/p are not implemented.";
545      " Please try (p^k,a) as ground field or use `reddevelop'.";
546      return(return_error);
547    }
548 }
549 //---- Ende der unzulaessigen Ringe; Ringwechsel in einen guenstigen Ring: ---
550
551 int ringwechsel=(varstr(basering)!="x,y") or (ordstr(basering)!="ls(2),C");
552
553 def altring = basering;
554 if (ringwechsel) {
555   string mipl=string(minpoly);
556   execute("ring guenstig = ("+charstr(altring)+"),(x,y),ls;");
557   if ((char(basering)==0) && (mipl!="0")) {
558     execute("minpoly="+mipl+";");
559   }}
560 else { def guenstig=basering; }
561 export guenstig;
562
563 //-------------------------- Initialisierungen -------------------------------
564 map m=altring,x,y;
565 if (ringwechsel) { poly f=m(f); }
566 if (defined(HNDebugOn))
567 {"received polynomial: ",f,", where x =",namex,", y =",namey;}
568
569 int M,N,Q,R,l,e,hilf,eps,getauscht,Abbruch,zeile,exponent,Ausgabe;
570
571 // Werte von Ausgabe: 0 : normale HNE-Matrix,
572 // 1 : Fehler aufgetreten - Matrix (namey) zurueck
573 // 2 : Die HNE ist eine Nullzeile - Matrix (0) zurueck
574 // int maxspalte=1; geaendert: wird jetzt am Anfang gesetzt
575
576 int minimalHNE=0;          // Flag fuer minimale HNE-Berechnung
577 int einzweig=1;            // Flag fuer Irreduzibilit"at
578 intvec hqs;                // erhaelt die Werte von h(zeile)=Q;
579
580 if (maxspalte<0) {
581   minimalHNE=1;
582   maxspalte=1;
583 }
584
585 number c,delta;
586 int p = char(basering);
587 string ringchar=charstr(basering);
588 map xytausch = basering,y,x;
589 if ((p!=0) and (ringchar != string(p))) {
590                            // coefficient field is extension of Z/pZ
591   execute("int n_elements="+
592           ringchar[1,size(ringchar)-size(parstr(basering))-1]+";");
593                            // number of elements of actual ring
594   number generat=par(1);   // generator of the coefficient field of the ring
595 }
596
597
598 //========= Abfangen von unzulaessigen oder trivialen Eingaben ===============
599 //------------ Nullpolynom oder Einheit im Potenzreihenring: -----------------
600 if (f == 0) {
601   dbprint(printlevel+1,"You have given me the zero-polynomial !");
602   Abbruch=1; Ausgabe=1;
603 }
604 else {
605   intvec nm = getnm(f);
606   N = nm[1]; M = nm[2]; // Berechne Schnittpunkte Newtonpolygon mit Achsen
607   if (N == 0) {
608     dbprint(printlevel+1,"The given polynomial is a unit as power series !");
609     Abbruch=1; Ausgabe=1;
610   }
611   else {
612    if (N == -1) {
613      if ((voice==2) && (printlevel > -1)) { "The HNE is x = 0"; }
614      Abbruch=1; Ausgabe=2; getauscht=1;
615      if (M <> 1) { einzweig=0; }
616    }
617    else {
618     if (M == -1) {
619       if ((voice==2) && (printlevel > -1)) { "The HNE is y = 0"; }
620       Abbruch=1; Ausgabe=2;
621       if (N <> 1) { einzweig=0; }
622   }}}
623 }
624 //--------------------- Test auf Quadratfreiheit -----------------------------
625 if (Abbruch==0) {
626
627 //-------- Fall basering==0,... : Wechsel in Ring mit char >0 ----------------
628 // weil squarefree eine Standardbasis berechnen muss (verwendet Syzygien)
629 // -- wenn f in diesem Ring quadratfrei ist, dann erst recht im Ring guenstig
630 //----------------------------------------------------------------------------
631
632  if ((p==0) and (size(charstr(basering))==1)) {
633   int testerg=(polytest(f)==0);
634   ring zweitring = 32003,(x,y),dp;
635   map polyhinueber=guenstig,x,y;     // fetch geht nicht
636   poly f=polyhinueber(f);
637   poly test_sqr=squarefree(f);
638   if (test_sqr != f) {
639    if (printlevel>0) {
640      "Most probably the given polynomial is not squarefree. But the test was";
641      "made in characteristic 32003 and not 0 to improve speed. You can";
642      "(r) redo the test in char 0 (but this may take some time)";
643      "(c) continue the development, if you're sure that the polynomial",
644      "IS squarefree";
645      if (testerg==1) {
646        "(s) continue the development with a squarefree factor (*)";}
647      "(q) or just quit the algorithm (default action)";
648      "";"Please enter the letter of your choice:";
649      string str=read("")[1];
650    }
651    else { string str="r"; }      // printlevel <= 0: non-interactive behaviour
652    setring guenstig;
653    map polyhinueber=zweitring,x,y;
654    if (str=="r") {
655      poly test_sqr=squarefree(f);
656      if (test_sqr != f) {
657       if (printlevel>0) { "The given polynomial is in fact not squarefree."; }
658       else              { "The given polynomial is not squarefree!"; }
659       "I'll continue with the radical.";
660       if (printlevel>0) { pause("Hit RETURN to continue:"); }
661       f=test_sqr;
662      }
663      else {
664       dbprint(printlevel,
665        "everything is ok -- the polynomial is squarefree in char(k)=0");
666      }
667    }
668    else {
669      if ((str=="s") and (testerg==1)) {
670       "(*) attention: it could be that the factor is only one in char 32003!";
671        f=polyhinueber(test_sqr);
672      }
673      else {
674        if (str<>"c") {
675          setring altring;kill guenstig;kill zweitring;
676          return(return_error);}
677        else { "if the algorithm doesn't terminate, you were wrong...";}
678    }}
679    kill zweitring;
680    nm = getnm(f);             // N,M haben sich evtl. veraendert
681    N = nm[1]; M = nm[2];      // Berechne Schnittpunkte Newtonpoly mit Achsen
682    if (defined(HNDebugOn)) {"I continue with the polynomial",f; }
683   }
684   else {
685     setring guenstig;
686     kill zweitring;
687   }
688  }
689 // ------------------- Fall Charakteristik > 0 -------------------------------
690  else {
691   poly test_sqr=squarefree(f);
692   if (test_sqr == 1) {
693    "The given polynomial is of the form g^"+string(p)+", therefore",
694    "reducible.";"Please try again.";
695    setring altring;
696    kill guenstig;
697    return(return_error);}
698   if (test_sqr != f) {
699    "The given polynomial is not squarefree. I'll continue with the radical.";
700    if (p != 0)
701     {"But if the polynomial contains a factor of the form g^"+string(p)+",";
702      "this factor will be lost.";}
703    if (printlevel>0) { pause("Hit RETURN to continue:"); }
704    f=test_sqr;
705    nm = getnm(f);              // N,M haben sich veraendert
706    N = nm[1]; M = nm[2];       // Berechne Schnittpunkte Newtonpoly mit Achsen
707    if (defined(HNDebugOn)) {"I continue with the polynomial",f; }
708   }
709
710  }                             // endelse(p==0)
711
712  if (N==0) {
713    " Sorry. The remaining polynomial is a unit in the power series ring...";
714    setring altring;kill guenstig;return(return_error);
715  }
716 //---------------------- gewaehrleiste, dass x transvers ist -----------------
717  if (M < N)
718  { f = xytausch(f);            // Variablentausch : x jetzt transvers
719    getauscht = 1;              // den Tausch merken
720    M = M+N; N = M-N; M = M-N;  // M, N auch vertauschen
721  }
722  if (defined(HNDebugOn)) {
723   if (getauscht) {"x<->y were exchanged; poly is now ",f;}
724   else           {"x , y were not exchanged";}
725   "M resp. N are now",M,N;
726  }
727 }                              // end(if Abbruch==0)
728
729 ideal a(0);
730 while (Abbruch==0) {
731
732 //================= Beginn der Schleife (eigentliche Entwicklung) ============
733
734 //------------------- ist das Newtonpolygon eine gerade Linie? ---------------
735  if (testreducible(f,N,M)) {
736    dbprint(printlevel+1," The given polynomial is not irreducible");
737    kill guenstig;
738    setring altring;
739    return(return_error);       // Abbruch der Prozedur!
740  }
741  R = M%N;
742  Q = M / N;
743
744 //-------------------- Fall Rest der Division R = 0 : ------------------------
745  if (R == 0) {
746    c = koeff(f,0,N);
747    if (c == 0) {"Something has gone wrong! I didn't get N correctly!"; exit;}
748    e = gcd(M,N);
749 //----------------- Test, ob leitf = c*(y^N - delta*x^(m/e))^e ist -----------
750    if (p==0) {
751      delta = koeff(f,M/ e,N - N/ e) / (-1*e*c);
752      if (defined(HNDebugOn)) {"quasihomogeneous leading form:",
753         leit(f,N,M)," = ",c,"* (y -",delta,"* x^"+string(M/ e)+")^",e," ?";}
754      if (leit(f,N,M) != c*(y^(N/ e) - delta*x^(M/ e))^e) {
755        dbprint(printlevel+1," The given polynomial is reducible !");
756        Abbruch=1; Ausgabe=1; }
757    }
758    else {                     // p!=0
759      if (e%p != 0) {
760        delta = koeff(f,M/ e,N - N/ e) / (-1*e*c);
761        if (defined(HNDebugOn)) {"quasihomogeneous leading form:",
762           leit(f,N,M)," = ",c,"* (y -",delta,"* x^"+string(M/ e)+")^",e," ?";}
763        if (leit(f,N,M) != c*(y^(N/ e) - delta*x^(M/ e))^e) {
764           dbprint(printlevel+1," The given polynomial is reducible !");
765           Abbruch=1; Ausgabe=1; }
766      }
767
768      else {                   // e%p == 0
769        eps = e;
770        for (l = 0; eps%p == 0; l=l+1) { eps=eps/ p;}
771        if (defined(HNDebugOn)) {e," -> ",eps,"*",p,"^",l;}
772        delta = koeff(f,(M/ e)*p^l,(N/ e)*p^l*(eps-1)) / (-1*eps*c);
773
774        if ((ringchar != string(p)) and (delta != 0)) {
775 //- coeff. field is not Z/pZ => we`ve to correct delta by taking (p^l)th root-
776          if (delta == generat) {exponent=1;}
777          else {
778           if (delta == 1) {exponent=0;}
779           else {
780            exponent=pardeg(delta);
781
782 //-- an dieser Stelle kann ein Fehler auftreten, wenn wir eine transzendente -
783 //-- Erweiterung von Z/pZ haben: dann ist das hinzuadjungierte Element kein  -
784 //-- Erzeuger der mult. Gruppe, d.h. in Z/pZ (a) gibt es i.allg. keinen      -
785 //-- Exponenten mit z.B. a2+a = a^exp                                        -
786 //----------------------------------------------------------------------------
787          }}
788          delta = generat^(extgcd(n_elements-1,p^l)[3]*exponent);
789        }
790
791        if (defined(HNDebugOn)) {"quasihomogeneous leading form:",
792          leit(f,N,M)," = ",c,"* (y^"+string(N/ e),"-",delta,"* x^"
793          +string(M/ e)+")^",e,"  ?";}
794        if (leit(f,N,M) != c*(y^(N/ e) - delta*x^(M/ e))^e) {
795          dbprint(printlevel+1," The given polynomial is reducible !");
796          Abbruch=1; Ausgabe=1; }
797      }
798    }
799    if (Abbruch == 0) {
800      f = T1_Transform(f,delta,M/ e);
801      if ((voice==2) && (printlevel > -1))
802       { "a("+string(zeile)+","+string(Q)+") =",delta; }
803      a(zeile)[Q]=delta;
804      if (defined(HNDebugOn)) {"transformed polynomial: ",f;}}
805
806      nm=getnm(f); N=nm[1]; M=nm[2];        // Neuberechnung des Newtonpolygons
807  }
808 //--------------------------- Fall R > 0 : -----------------------------------
809  else {
810    if ((voice==2) && (printlevel > -1)) { "h("+string(zeile)+") =",Q; }
811    hqs[zeile+1]=Q;                  // denn zeile beginnt mit dem Wert 0
812    a(zeile)[Q+1]=x;                 // Markierung des Zeilenendes der HNE
813    maxspalte=maxspalte*((Q+1) < maxspalte) + (Q+1)*((Q+1) >= maxspalte);
814                                     // Anpassung der Sp.zahl der HNE-Matrix
815    f = T_Transform(f,Q,N);
816    if (defined(HNDebugOn)) {"transformed polynomial: ",f;}
817    zeile=zeile+1;
818 //------------ Bereitstellung von Speicherplatz fuer eine neue Zeile: --------
819    ideal a(zeile);
820    M=N;N=R;
821  }
822
823 //--------------- schneidet das Newtonpolygon beide Achsen? ------------------
824  if (M==-1) {
825     if ((voice==2) && (printlevel > -1)) { "The HNE is finite!"; }
826     a(zeile)[Q+1]=x;   // Markiere das Ende der Zeile
827     hqs[zeile+1]=Q;
828     maxspalte=maxspalte*((Q+1) < maxspalte) + (Q+1)*((Q+1) >= maxspalte);
829     if (N <> 1) { einzweig=0; }
830     f=0;               // transformiertes Polynom wird nicht mehr gebraucht
831     Abbruch=1;
832  }
833  else {if (M<N) {"Something has gone wrong: M<N";}}
834  if(defined(HNDebugOn)) {"new M,N:",M,N;}
835
836 //----------------- Abbruchbedingungen fuer die Schleife: --------------------
837  if ((N==1) and (Abbruch!=1) and ((M > maxspalte) or (minimalHNE==1))
838      and (size(a(zeile))>0))
839 //----------------------------------------------------------------------------
840 // Abbruch, wenn die Matrix so voll ist, dass eine neue Spalte angefangen
841 // werden muesste und die letzte Zeile nicht nur Nullen enthaelt
842 // oder wenn die Matrix nicht voll gemacht werden soll (minimale Information)
843 //----------------------------------------------------------------------------
844   { Abbruch=1; hqs[zeile+1]=-1;
845     if (maxspalte < ncols(a(zeile))) { maxspalte=ncols(a(zeile));}
846     if ((minimalHNE==1) and (M <= maxspalte)) {
847 // teile param mit, dass Eintraege der letzten Zeile nur teilw. richtig sind:-
848       hqs[zeile+1]=-M;
849 //------------- markiere den Rest der Zeile als unbekannt: -------------------
850       for (R=M; R <= maxspalte; R++) { a(zeile)[R]=y;}
851     }                  // R wird nicht mehr gebraucht
852   }
853 //========================= Ende der Schleife ================================
854
855 }
856 setring altring;
857 if (Ausgabe == 0) {
858 //-------------------- Ergebnis in den alten Ring transferieren: -------------
859   map zurueck=guenstig,maxideal(1)[1],maxideal(1)[2];
860   matrix amat[zeile+1][maxspalte];
861   ideal uebergabe;
862   for (e=0; e<=zeile; e=e+1) {
863     uebergabe=zurueck(a(e));
864     if (ncols(uebergabe) > 1) {
865      amat[e+1,1..ncols(uebergabe)]=uebergabe;}
866     else {amat[e+1,1]=uebergabe[1];}
867   }
868   if (ringwechsel) {
869     if (nvars(altring)==2) { f=fetch(guenstig,f); }
870     else                   { f=zurueck(f); }
871   }
872 }
873
874 kill guenstig;
875 if ((einzweig==0) && (voice==2) && (printlevel > -1)) {
876    "// Note: The curve is reducible, but we were able to compute a HNE.";
877    "// This means the result is only one of several existing HNE's.";
878 }
879 if (Ausgabe == 0) { return(list(amat,hqs,getauscht,f,einzweig));}
880 if (Ausgabe == 1) { return(return_error);}             // error has occurred
881 if (Ausgabe == 2) { return(list(matrix(ideal(0,x)),intvec(1),getauscht,
882                                 poly(0),einzweig));}   // HNE is x=0 or y=0
883}
884example
885{ "EXAMPLE:"; echo = 2;
886  ring exring = 7,(x,y),ds;
887  list hne=develop(4x98+2x49y7+x11y14+2y14);
888  print(hne[1]);
889  // therefore the HNE is:
890  // z(-1)= 3*z(0)^7 + z(0)^7*z(1),
891  // z(0) = z(1)*z(2),
892  //        (note that there is 1 zero in the 2nd row before x)
893  // z(1) = z(2)^3*z(3),    (there are 3 zeroes in the 3rd row)
894  // z(2) = z(3)*z(4),
895  // z(3) = -z(4)^2 + 0*z(4)^3 +...+ 0*z(4)^8 + ?*z(4)^9 + ...
896  //   (the missing x in the matrix indicates that this line
897  //    is not complete. It can only occur in the last line of the
898  //    HNE, and normally does.)
899  hne[2];
900  param(hne);
901  // returns the parametrization
902  // x(t)= -t^14+O(t^21),  y(t)= -3t^98+O(t^105)
903  // (the term -t^109 in y may have a wrong coefficient)
904  displayHNE(hne);
905}
906
907///////////////////////////////////////////////////////////////////////////////
908//               procedures to extract information out of HNE                //
909///////////////////////////////////////////////////////////////////////////////
910
911proc param
912"USAGE:  param(l [,x]) takes the output of develop(f)
913        (list l (matrix m, intvec v, int s[,poly g,...]))
914        and gives a parametrization for f; the first variable of the active
915        ring is chosen as indefinite. If the ring contains more than
916        two variables, the 3rd variable is chosen (remember that develop takes
917        the first two variables and therefore the other vars should be unused).
918 @*     x is an optional parameter of any type.
919RETURN: If only the list l is given:
920        ideal of two polynomials: if the HNE was finite, f(param[1],param[2])
921        will be  zero. If not, the real parametrization will be
922        two power series; then param will return a truncation of these series.
923
924        If the optional parameter x is given:
925        list L with L[1]=param(l) (the ideal containing the parametrization)
926        and L[2]=intvec with two entries indicating the highest degree unto
927        which the coefficients of the monomials in L[1] are exact (a value of
928        -1 is for infinity, i.e. the corresponding polynomial is exact).
929SEE ALSO: develop, extdevelop
930KEYWORDS: parametrization
931EXAMPLE: example param;     shows an example
932         example develop;   shows another example
933"
934{
935 //-------------------------- Initialisierungen -------------------------------
936 if (typeof(#[1])=="list") {
937   list Li=#[1];
938   matrix m=Li[1];
939   intvec v=Li[2];
940   int switch=Li[3];
941   int return_list=1;
942 }
943 else {
944   matrix m=#[1];
945   intvec v=#[2];
946   int switch=#[3];
947   int return_list=0;
948 }
949 if (switch==-1) {
950   "An error has occurred in develop, so there is no HNE.";
951   return(ideal(0,0));
952 }
953 int fehler,fehlervor,untergrad,untervor,beginn,i,zeile,hilf;
954
955 if (nvars(basering) > 2) { poly z(size(v)+1)=var(3); }
956 else                     { poly z(size(v)+1)=var(1); }
957 poly z(size(v));
958 zeile=size(v);
959 //------------- Parametrisierung der untersten Zeile der HNE -----------------
960 if (v[zeile] > 0) {
961   fehler=0;           // die Parametrisierung wird exakt werden
962   for (i=1; i<=v[zeile]; i++) {
963     z(zeile)=z(zeile)+m[zeile,i]*z(zeile+1)^i;
964 }}
965 else {
966   untervor=1;         // = Untergrad der vorhergehenden Zeile
967   if (v[zeile]==-1) {
968     fehler=ncols(m)+1;
969     for (i=1; i<=ncols(m); i++) {
970       z(zeile)=z(zeile)+m[zeile,i]*z(zeile+1)^i;
971       if ((untergrad==0) and (m[zeile,i]!=0)) {untergrad=i;}
972                       // = Untergrad der aktuellen Zeile
973   }}
974   else {
975     fehler= -v[zeile];
976     for (i=1; i<-v[zeile]; i++) {
977       z(zeile)=z(zeile)+m[zeile,i]*z(zeile+1)^i;
978       if ((untergrad==0) and (m[zeile,i]!=0)) {untergrad=i;}
979   }}
980 }
981 //------------- Parametrisierung der restlichen Zeilen der HNE ---------------
982 for (zeile=size(v)-1; zeile>0; zeile--) {
983   poly z(zeile);
984   beginn=0;             // Beginn der aktuellen Zeile
985   for (i=1; i<=v[zeile]; i++) {
986     z(zeile)=z(zeile)+m[zeile,i]*z(zeile+1)^i;
987     if ((beginn==0) and (m[zeile,i]!=0)) { beginn=i;}
988   }
989   z(zeile)=z(zeile) + z(zeile+1)^v[zeile] * z(zeile+2);
990   if (beginn==0) {
991     if (fehler>0) {     // damit fehler=0 bleibt bei exakter Param.
992     fehlervor=fehler;   // Fehler der letzten Zeile
993     fehler=fehler+untergrad*(v[zeile]-1)+untervor;   // Fehler dieser Zeile
994     hilf=untergrad;
995     untergrad=untergrad*v[zeile]+untervor;
996     untervor=hilf;}}    // untervor = altes untergrad
997   else {
998     fehlervor=fehler;
999     fehler=fehler+untergrad*(beginn-1);
1000     untervor=untergrad;
1001     untergrad=untergrad*beginn;
1002 }}
1003 //--------------------- Ausgabe der Fehlerabschaetzung -----------------------
1004 if (switch==0) {
1005   if (fehler>0) {
1006     if (fehlervor>0) {
1007       if ((voice==2) && (printlevel > -1)) {
1008         "// ** Warning: result is exact up to order",fehlervor-1,"in",
1009         maxideal(1)[1],"and",fehler-1,"in",maxideal(1)[2],"!";
1010     }}
1011     else {
1012       if ((voice==2) && (printlevel > -1)) {
1013         "// ** Warning: result is exact up to order",fehler-1,"in",
1014         maxideal(1)[2],"!";
1015     }}
1016   }
1017   if (return_list==0) { return(ideal(z(2),z(1))); }
1018   else   { return(list(ideal(z(2),z(1)),intvec(fehlervor-1,fehler-1))); }
1019 }
1020 else {
1021   if (fehler>0) {
1022     if (fehlervor>0) {
1023      if ((voice==2) && (printlevel > -1)) {
1024        "// ** Warning: result is exact up to order",fehler-1,"in",
1025        maxideal(1)[1],"and",fehlervor-1,"in",maxideal(1)[2],"!";
1026     }}
1027     else {
1028      if ((voice==2) && (printlevel > -1)) {
1029        "// ** Warning: result is exact up to order",fehler-1,"in",
1030        maxideal(1)[1],"!";
1031     }}
1032   }
1033   if (return_list==0) { return(ideal(z(1),z(2))); }
1034   else   { return(list(ideal(z(1),z(2)),intvec(fehler-1,fehlervor-1))); }
1035 }
1036}
1037example
1038{ "EXAMPLE:"; echo = 2;
1039 ring exring=0,(x,y,t),ds;
1040 poly f=x3+2xy2+y2;
1041 list hne=develop(f);
1042 list hne_extended1=develop(f,6);
1043 list hne_extended2=develop(f,10);
1044            //   compare the different matrices ...
1045 print(hne[1]);
1046 print(hne_extended1[1]);
1047 print(hne_extended2[1]);
1048            // ... and the resulting parametrizations:
1049 param(hne);
1050 param(hne_extended1);
1051 param(hne_extended2);
1052 param(hne_extended2,0);
1053}
1054///////////////////////////////////////////////////////////////////////////////
1055
1056proc invariants
1057"USAGE:   invariants(l) takes the output of develop(f)
1058         (list l (matrix m, intvec v, int s[,poly g,...]))
1059         and computes the following irreducible curve invariants:
1060RETURN:  a list, if l contains a valid HNE:
1061      @format
1062    - invariants(l)[1]: intvec         (characteristic exponents)
1063    - invariants(l)[2]: intvec         (generators of the semigroup)
1064    - invariants(l)[3],[4]: 2 x intvec (Puiseux pairs, 1st and 2nd components)
1065    - invariants(l)[5]: int            (degree of the conductor)
1066    - invariants(l)[6]: intvec         (sequence of multiplicities)
1067      @end format
1068         an empty list, if an error occurred in the procedure develop.
1069SEE ALSO: develop, displayInvariants, multsequence, intersection
1070KEYWORDS: characteristic exponents; semigroup of values; Puiseux pairs;
1071          conductor, degree; multiplicities, sequence of
1072EXAMPLE:  example invariants; shows an example
1073"
1074{
1075 //-------------------------- Initialisierungen -------------------------------
1076 matrix m=#[1];
1077 intvec v=#[2];
1078 int switch=#[3];
1079 list ergebnis;
1080 if (switch==-1) {
1081   "An error has occurred in develop, so there is no HNE.";
1082   return(ergebnis);
1083 }
1084 intvec beta,s,svorl,ordnung,multseq,mpuiseux,npuiseux,halbgr;
1085 int genus,zeile,i,j,k,summe,conductor,ggT;
1086 string Ausgabe;
1087 int nc=ncols(m); int nr=nrows(m);
1088 ordnung[nr]=1;
1089         // alle Indizes muessen (gegenueber [Ca]) um 1 erhoeht werden,
1090         // weil 0..r nicht als Wertebereich erlaubt ist (aber nrows(m)==r+1)
1091
1092 //---------------- Bestimme den Untergrad der einzelnen Zeilen ---------------
1093 for (zeile=nr; zeile>1; zeile--) {
1094   if ((size(ideal(m[zeile,1..nc])) > 1) or (zeile==nr)) { // keine Nullzeile
1095      k=1;
1096      while (m[zeile,k]==0) {k++;}
1097      ordnung[zeile-1]=k*ordnung[zeile]; // vgl. auch Def. von untergrad in
1098      genus++;                           // proc param
1099      svorl[genus]=zeile;} // werden gerade in umgekehrter Reihenfolge abgelegt
1100   else {
1101      ordnung[zeile-1]=v[zeile]*ordnung[zeile]+ordnung[zeile+1];
1102 }}
1103 //----------------- charakteristische Exponenten (beta) ----------------------
1104 s[1]=1;
1105 for (k=1; k <= genus; k++) { s[k+1]=svorl[genus-k+1];} // s[2]==s(1), u.s.w.
1106 beta[1]=ordnung[1]; //charakt. Exponenten: Index wieder verschoben
1107 for (k=1; k <= genus; k++) {
1108   summe=0;
1109   for (i=1; i <= s[k]; i++) {summe=summe+v[i]*ordnung[i];}
1110   beta[k+1]=summe+ordnung[s[k]]+ordnung[s[k]+1]-ordnung[1];
1111 }
1112 //--------------------------- Puiseuxpaare -----------------------------------
1113 int produkt=1;
1114 for (i=1; i<=genus; i++) {
1115   ggT=gcd(beta[1],beta[i+1]*produkt);
1116   mpuiseux[i]=beta[i+1]*produkt / ggT;
1117   npuiseux[i]=beta[1] / ggT;
1118   produkt=produkt*npuiseux[i];
1119 }
1120 //---------------------- Grad des Konduktors ---------------------------------
1121 summe=1-ordnung[1];
1122 if (genus > 0) {
1123   for (i=2; i <= genus+1; i++) {
1124     summe=summe + beta[i] * (ordnung[s[i-1]] - ordnung[s[i]]);
1125   }                              // n.b.: Indizierung wieder um 1 verschoben
1126 }
1127 conductor=summe;
1128 //------------------- Erzeuger der Halbgruppe: -------------------------------
1129 halbgr=puiseux2generators(mpuiseux,npuiseux);
1130
1131 //------------------- Multiplizitaetensequenz: -------------------------------
1132 k=1;
1133 for (i=1; i<size(v); i++) {
1134   for (j=1; j<=v[i]; j++) {
1135     multseq[k]=ordnung[i];
1136     k++;
1137 }}
1138 multseq[k]=1;
1139 //------------------------- Rueckgabe ----------------------------------------
1140 ergebnis=beta,halbgr,mpuiseux,npuiseux,conductor,multseq;
1141 return(ergebnis);
1142}
1143example
1144{ "EXAMPLE:"; echo = 2;
1145 ring exring=0,(x,y),dp;
1146 list hne=develop(y4+2x3y2+x6+x5y);
1147 list erg=invariants(hne);
1148 erg[1];                   // the characteristic exponents
1149 erg[2];                   // the generators of the semigroup of values
1150 erg[3],erg[4];            // the Puiseux pairs in packed form
1151 erg[5] / 2;               // the delta-invariant
1152 erg[6];                   // the sequence of multiplicities
1153                           // To display the invariants more 'nicely':
1154 displayInvariants(hne);
1155}
1156///////////////////////////////////////////////////////////////////////////////
1157
1158proc displayInvariants
1159"USAGE:   displayInvariants(l); takes the output both of
1160         develop(f) and reddevelop(f)
1161          ( list l (matrix m, intvec v, int s[,poly g,...])
1162            or list of lists in the form l )
1163RETURN:  nothing
1164DISPLAY: invariants of the corresponding branch, resp. of all branches,
1165         in a better readable form.
1166SEE ALSO: invariants, intersection, develop, reddevelop
1167EXAMPLE: example displayInvariants;  shows an example
1168"
1169{
1170 int i,j,k,mul;
1171 string Ausgabe;
1172 list ergebnis;
1173 //-- entferne ueberfluessige Daten zur Erhoehung der Rechengeschwindigkeit: --
1174 #=stripHNE(#);
1175 //-------------------- Ausgabe eines Zweiges ---------------------------------
1176 if (typeof(#[1])=="matrix") {
1177   ergebnis=invariants(#);
1178   if (size(ergebnis)!=0) {
1179    " characteristic exponents  :",ergebnis[1];
1180    " generators of semigroup   :",ergebnis[2];
1181    if (size(ergebnis[1])>1) {
1182     for (i=1; i<=size(ergebnis[3]); i++) {
1183       Ausgabe=Ausgabe+"("+string(ergebnis[3][i])+","
1184       +string(ergebnis[4][i])+")";
1185    }}
1186    " Puiseux pairs             :",Ausgabe;
1187    " degree of the conductor   :",ergebnis[5];
1188    " delta invariant           :",ergebnis[5]/2;
1189    " sequence of multiplicities:",ergebnis[6];
1190 }}
1191 //-------------------- Ausgabe aller Zweige ----------------------------------
1192 else {
1193  for (j=1; j<=size(#); j++) {
1194    ergebnis=invariants(#[j]);
1195    " --- invariants of branch number",j,": ---";
1196    " characteristic exponents  :",ergebnis[1];
1197    " generators of semigroup   :",ergebnis[2];
1198    Ausgabe="";
1199    if (size(ergebnis[1])>1) {
1200     for (i=1; i<=size(ergebnis[3]); i++) {
1201       Ausgabe=Ausgabe+"("+string(ergebnis[3][i])+","
1202       +string(ergebnis[4][i])+")";
1203    }}
1204    " Puiseux pairs             :",Ausgabe;
1205    " degree of the conductor   :",ergebnis[5];
1206    " delta invariant           :",ergebnis[5]/2;
1207    " sequence of multiplicities:",ergebnis[6];
1208    "";
1209  }
1210  if (size(#)>1) {
1211    " -------------- intersection multiplicities : -------------- ";"";
1212    Ausgabe="branch |   ";
1213    for (j=size(#); j>1; j--) {
1214      if (size(string(j))==1) { Ausgabe=Ausgabe+" "+string(j)+"    "; }
1215      else                    { Ausgabe=Ausgabe+string(j)+"    "; }
1216    }
1217    Ausgabe;
1218    Ausgabe="-------+";
1219    for (j=2; j<size(#); j++) { Ausgabe=Ausgabe+"------"; }
1220    Ausgabe=Ausgabe+"-----";
1221    Ausgabe;
1222  }
1223  for (j=1; j<size(#); j++) {
1224    if (size(string(j))==1) { Ausgabe="    "+string(j)+"  |"; }
1225    else                    { Ausgabe="   " +string(j)+"  |"; }
1226    for (k=size(#); k>j; k--) {
1227      mul=intersection(#[j],#[k]);
1228      for (i=1; i<=5-size(string(mul)); i++) { Ausgabe=Ausgabe+" "; }
1229      Ausgabe=Ausgabe+string(mul);
1230      if (k>j+1) { Ausgabe=Ausgabe+","; }
1231    }
1232    Ausgabe;
1233  }
1234 }
1235 return();
1236}
1237example
1238{ "EXAMPLE:"; echo = 2;
1239 ring exring=0,(x,y),dp;
1240 list hne=develop(y4+2x3y2+x6+x5y);
1241 displayInvariants(hne);
1242}
1243///////////////////////////////////////////////////////////////////////////////
1244
1245proc multiplicities
1246"USAGE:   multiplicities(l) takes the output of develop(f)
1247         (list l (matrix m, intvec v, int s[,poly g,...]))
1248RETURN:  intvec of the different multiplicities that occur during the
1249         successive blowing up of the curve corresponding to f
1250SEE ALSO: develop
1251EXAMPLE: example multiplicities;  shows an example
1252"
1253{
1254 matrix m=#[1];
1255 intvec v=#[2];
1256 int switch=#[3];
1257 list ergebnis;
1258 if (switch==-1) {
1259   "An error has occurred in develop, so there is no HNE.";
1260   return(intvec(0));
1261 }
1262 intvec ordnung;
1263 int zeile,k;
1264 int nc=ncols(m); int nr=nrows(m);
1265 ordnung[nr]=1;
1266 //---------------- Bestimme den Untergrad der einzelnen Zeilen ---------------
1267 for (zeile=nr; zeile>1; zeile--) {
1268   if ((size(ideal(m[zeile,1..nc])) > 1) or (zeile==nr)) { // keine Nullzeile
1269      k=1;
1270      while (m[zeile,k]==0) {k++;}
1271      ordnung[zeile-1]=k*ordnung[zeile];
1272   }
1273   else {
1274      ordnung[zeile-1]=v[zeile]*ordnung[zeile]+ordnung[zeile+1];
1275 }}
1276 return(ordnung);
1277}
1278example
1279{ "EXAMPLE:"; echo = 2;
1280  int p=printlevel; printlevel=-1;
1281  ring r=0,(x,y),dp;
1282  multiplicities(develop(x5+y7));
1283  // The first value is the multiplicity of the curve itself, here it's 5
1284  printlevel=p;
1285}
1286///////////////////////////////////////////////////////////////////////////////
1287
1288proc puiseux2generators (intvec m, intvec n)
1289"USAGE:   puiseux2generators(m,n);
1290         m,n intvecs with 1st resp. 2nd components of Puiseux pairs
1291RETURN:  intvec of the generators of the semigroup of values
1292SEE ALSO: invariants
1293EXAMPLE: example puiseux2generators;  shows an example
1294"
1295{
1296 intvec beta;
1297 int q=1;
1298 //------------ glatte Kurve (eigentl. waeren m,n leer): ----------------------
1299 if (m==0) { return(intvec(1)); }
1300 //------------------- singulaere Kurve: --------------------------------------
1301 for (int i=1; i<=size(n); i++) { q=q*n[i]; }
1302 beta[1]=q; // == q_0
1303 m=1,m; n=1,n; // m[1] ist damit m_0 usw., genau wie beta[1]==beta_0
1304 for (i=2; i<=size(n); i++) {
1305  beta[i]=m[i]*q/n[i] - m[i-1]*q + n[i-1]*beta[i-1];
1306  q=q/n[i]; // == q_i
1307 }
1308 return(beta);
1309}
1310example
1311{ "EXAMPLE:"; echo = 2;
1312  // take (3,2),(7,2),(15,2),(31,2),(63,2),(127,2) as Puiseux pairs:
1313  puiseux2generators(intvec(3,7,15,31,63,127),intvec(2,2,2,2,2,2));
1314}
1315///////////////////////////////////////////////////////////////////////////////
1316
1317proc intersection (list hn1, list hn2)
1318"USAGE:   intersection(hne1,hne2);
1319         hne1,hne2: two lists representing a HNE (normally two entries out of
1320         the output of reddevelop), i.e. list(matrix,intvec,int[,poly]).
1321RETURN:  The intersection multiplicity of the branches corresponding to
1322         hne1 & hne2 (of type int).
1323SEE ALSO: reddevelop, displayInvariants
1324KEYWORDS: intersection multiplicity
1325EXAMPLE: example intersection;  shows an example
1326"
1327{
1328 //------------------ `intersect' ist schon reserviert ... --------------------
1329 int i,j,s,sum,schnitt,unterschied;
1330 matrix a1=hn1[1];
1331 matrix a2=hn2[1];
1332 intvec h1=hn1[2];
1333 intvec h2=hn2[2];
1334 intvec n1=multiplicities(hn1);
1335 intvec n2=multiplicities(hn2);
1336 if (hn1[3]!=hn2[3]) {
1337 //-- die jeweils erste Zeile von hn1,hn2 gehoert zu verschiedenen Parametern -
1338 //---------------- d.h. beide Kurven schneiden sich transversal --------------
1339   schnitt=n1[1]*n2[1];        // = mult(hn1)*mult(hn2)
1340 }
1341 else {
1342 //--------- die jeweils erste Zeile gehoert zum gleichen Parameter -----------
1343   unterschied=0;
1344   for (s=1; (h1[s]==h2[s]) && (s<size(h1)) && (s<size(h2))
1345              && (unterschied==0); s++) {
1346     for (i=1; (a1[s,i]==a2[s,i]) && (i<=h1[s]); i++) {;}
1347     if (i<=h1[s]) {
1348       unterschied=1;
1349       s--;                    // um s++ am Schleifenende wieder auszugleichen
1350     }
1351   }
1352   if (unterschied==0) {
1353     if ((s<size(h1)) && (s<size(h2))) {
1354       for (i=1; (a1[s,i]==a2[s,i]) && (i<=h1[s]) && (i<=h2[s]); i++) {;}
1355     }
1356     else {
1357 //-------------- Sonderfall: Unterschied in letzter Zeile suchen -------------
1358 // Beachte: Es koennen undefinierte Stellen auftreten, bei abbrechender HNE
1359 // muss die Ende-Markierung weg, h_[r] ist unendlich, die Matrix muss mit
1360 // Nullen fortgesetzt gedacht werden
1361 //----------------------------------------------------------------------------
1362       if (ncols(a1)>ncols(a2)) { j=ncols(a1); }
1363       else                     { j=ncols(a2); }
1364       unterschied=0;
1365       if ((h1[s]>0) && (s==size(h1))) {
1366         a1[s,h1[s]+1]=0;
1367         if (ncols(a1)<=ncols(a2)) { unterschied=1; }
1368       }
1369       if ((h2[s]>0) && (s==size(h2))) {
1370         a2[s,h2[s]+1]=0;
1371         if (ncols(a2)<=ncols(a1)) { unterschied=1; }
1372       }
1373       if (unterschied==1) {                   // mind. eine HNE war endlich
1374         matrix ma1[1][j]=a1[s,1..ncols(a1)];  // und bedarf der Fortsetzung
1375         matrix ma2[1][j]=a2[s,1..ncols(a2)];  // mit Nullen
1376       }
1377       else {
1378         if (ncols(a1)>ncols(a2)) { j=ncols(a2); }
1379         else                     { j=ncols(a1); }
1380         matrix ma1[1][j]=a1[s,1..j];          // Beschr. auf vergleichbaren
1381         matrix ma2[1][j]=a2[s,1..j];          // Teil (der evtl. y's enth.)
1382       }
1383       for (i=1; (ma1[1,i]==ma2[1,i]) && (i<j) && (ma1[1,i]!=var(2)); i++) {;}
1384       if (ma1[1,i]==ma2[1,i]) {
1385         "//** The two HNE's are identical!";
1386         "//** You have either tried to intersect a branch with itself,";
1387         "//** or the two branches have been developed separately.";
1388         "//   In the latter case use `extdevelop' to extend the HNE's until",
1389         "they differ.";
1390         return(-1);
1391       }
1392       if ((ma1[1,i]==var(2)) || (ma2[1,i]==var(2))) {
1393         "//** The two HNE's are (so far) identical. This is because they",
1394         "have been";
1395         "//** computed separately. I need more data; use `extdevelop' to",
1396         "extend them,";
1397         if (ma1[1,i]==var(2)) {"//** at least the first one.";}
1398         else                  {"//** at least the second one.";}
1399         return(-1);
1400       }
1401     }
1402   }
1403   sum=0;
1404   h1[size(h1)]=ncols(a1)+42;        // Ersatz fuer h1[r]=infinity
1405   h2[size(h2)]=ncols(a2)+42;
1406   for (j=1; j<s; j++) {sum=sum+h1[j]*n1[j]*n2[j];}
1407   if ((i<=h1[s]) && (i<=h2[s]))    { schnitt=sum+i*n1[s]*n2[s]; }
1408   if (i==h2[s]+1) { schnitt=sum+h2[s]*n1[s]*n2[s]+n2[s+1]*n1[s]; }
1409   if (i==h1[s]+1) { schnitt=sum+h1[s]*n2[s]*n1[s]+n1[s+1]*n2[s]; }
1410 // "s:",s-1,"i:",i,"S:",sum;
1411 }
1412 return(schnitt);
1413}
1414example
1415{
1416  // -------- prepare for example ---------
1417  if (nameof(basering)=="HNEring") {
1418   def rettering=HNEring;
1419   kill HNEring;
1420  }
1421  // ------ the example starts here -------
1422  "EXAMPLE:"; echo = 2;
1423  ring r=0,(x,y),dp;
1424  list hne=reddevelop((x2-y3)*(x2+y3));
1425  intersection(hne[1],hne[2]);
1426  kill HNEring,r;
1427  echo = 0;
1428  // --- restore HNEring if previously defined ---
1429  if (defined(rettering)) {
1430   setring rettering;
1431   def HNEring=rettering;
1432   export HNEring;
1433  }
1434}
1435///////////////////////////////////////////////////////////////////////////////
1436
1437proc multsequence
1438"USAGE:   multsequence(l);
1439         l is the output of either develop(f) or reddevelop(f)
1440RETURN:  - if l=@code{develop}(f) or l=@code{reddevelop}(f)[i]:
1441           intvec of the sequence of multiplicities of the curve
1442           resp. of the i-th branch (the same as @code{invariants}(l)[6]; )
1443
1444         - if l=@code{reddevelop}(f) : list of two integer matrices:
1445  @* @code{multsequence}(l)[1][i,*] contains the multiplicities of the branches
1446           at their infinitely near point of 0 in its (i-1) order
1447           neighbourhood (i.e. i=1: multiplicity of the branches themselves,
1448                 i=2: multiplicity of their 1st quadratic transformed etc.,
1449       @*  or to say it in another way: @code{multsequence}(l)[1][*,j] is the
1450                 sequence of multiplicities of the j-th branch).
1451  @* @code{multsequence}(l)[2][i,*] contains the information which of these
1452           infinitely near points coincide.
1453NOTE:  The order of elements of the list obtained from @code{reddevelop} must
1454       not be changed (because then the coincident infinitely near points
1455       couldn't be grouped together, cf. meaning of 2nd intmat in example).
1456       Hence it is not wise to compute the HNE of several polynomials
1457       separately, put them into a list l and call @code{multsequence}(l).
1458
1459       Use @code{displayMultsequence} to produce a better readable output for
1460       reducible curves on the screen.
1461SEE ALSO: displayMultsequence, develop, reddevelop, separateHNE
1462EXAMPLE: example multsequence;  shows an example
1463"
1464{
1465 //-- entferne ueberfluessige Daten zur Erhoehung der Rechengeschwindigkeit: --
1466 #=stripHNE(#);
1467 int k,i,j;
1468 //----------------- Multiplizitaetensequenz eines Zweiges --------------------
1469 if (typeof(#[1])=="matrix") {
1470  intvec v=#[2];
1471  list ergebnis;
1472  if (#[3]==-1) {
1473    "An error has occurred in develop, so there is no HNE.";
1474   return(intvec(0));
1475  }
1476  intvec multips,multseq;
1477  multips=multiplicities(#);
1478  k=1;
1479  for (i=1; i<size(v); i++) {
1480    for (j=1; j<=v[i]; j++) {
1481      multseq[k]=multips[i];
1482      k++;
1483  }}
1484  multseq[k]=1;
1485  return(multseq);
1486 }
1487 //---------------------------- mehrere Zweige --------------------------------
1488 else {
1489   list HNEs=#;
1490   int anzahl=size(HNEs);
1491   int maxlength=0;
1492   int bisher;
1493   intvec schnitt,ones;
1494   ones[anzahl]=0;
1495   ones=ones+1;                  // = 1,1,...,1
1496   for (i=1; i<anzahl; i++) {
1497     schnitt[i]=separateHNE(HNEs[i],HNEs[i+1]);
1498     j=size(multsequence(HNEs[i]));
1499     maxlength=maxlength*(j < maxlength) + j*(j >= maxlength);
1500     maxlength=maxlength*(schnitt[i]+1 < maxlength)
1501               + (schnitt[i]+1)*(schnitt[i]+1 >= maxlength);
1502   }
1503   j=size(multsequence(HNEs[anzahl]));
1504   maxlength=maxlength*(j < maxlength) + j*(j >= maxlength);
1505
1506//-------------- Konstruktion der ersten zu berechnenden Matrix ---------------
1507   intmat allmults[maxlength][anzahl];
1508   for (i=1; i<=maxlength; i++)  { allmults[i,1..anzahl]=ones[1..anzahl]; }
1509   for (i=1; i<=anzahl; i++) {
1510     ones=multsequence(HNEs[i]);
1511     allmults[1..size(ones),i]=ones[1..size(ones)];
1512   }
1513//---------------------- Konstruktion der zweiten Matrix ----------------------
1514   intmat separate[maxlength][anzahl];
1515   for (i=1; i<=maxlength; i++) {
1516     k=1;
1517     bisher=0;
1518     if (anzahl==1) { separate[i,1]=1; }
1519     for (j=1; j<anzahl; j++)   {
1520       if (schnitt[j]<i) {
1521         separate[i,k]=j-bisher;
1522         bisher=j;
1523         k++;
1524       }
1525       separate[i,k]=anzahl-bisher;
1526     }
1527   }
1528  return(list(allmults,separate));
1529 }
1530}
1531example
1532{
1533  // -------- prepare for example ---------
1534  if (nameof(basering)=="HNEring") {
1535   def rettering=HNEring;
1536   kill HNEring;
1537  }
1538  // ------ the example starts here -------
1539  "EXAMPLE:"; echo = 2;
1540  ring r=0,(x,y),dp;
1541  list hne=reddevelop((x6-y10)*(x+y2-y3)*(x+y2+y3));
1542
1543  multsequence(hne[1]),"  |  ",multsequence(hne[2]),"  |  ",
1544  multsequence(hne[3]),"  |  ",multsequence(hne[4]);
1545  multsequence(hne);
1546  // The meaning of the entries of the 2nd matrix is as follows:
1547  displayMultsequence(hne);
1548  kill HNEring,r;
1549  echo = 0;
1550  // --- restore HNEring if previously defined ---
1551  if (defined(rettering)) {
1552   setring rettering;
1553   def HNEring=rettering;
1554   export HNEring;
1555  }
1556}
1557///////////////////////////////////////////////////////////////////////////////
1558
1559proc displayMultsequence
1560"USAGE:   displayMultsequence(l);
1561         l is the output of either develop(f) or reddevelop(f)
1562RETURN:  nothing
1563DISPLAY: the sequence of multiplicities:
1564       if l=develop(f) or l=reddevelop(f)[i] : just the sequence a,b,c,...,1
1565 @*    if l=reddevelop(f) : a sequence of the following form:
1566
1567 @*    @math{[(a_1,....,b_1,....,c_1)]},
1568 @*    @math{[(a_2,...),...,(...,c_2)]},
1569 @*    @math{   ...................}
1570 @*    @math{[(a_n),(b_n),.....,(c_n)]}
1571
1572 @*    with @math{a_1,...,a_n} the sequence of multiplicities of the 1st branch
1573 @*    [...] the multiplicities of the j-th transformed of all branches
1574 @*    (...) the multiplicities of those branches meeting in the same
1575             infinitely near point.
1576NOTE:    The same restrictions for l as in `@code{multsequence}' apply.
1577SEE ALSO: multsequence, develop, reddevelop, separateHNE
1578EXAMPLE: example displayMultsequence;  shows an example
1579"
1580{
1581 //-- entferne ueberfluessige Daten zur Erhoehung der Rechengeschwindigkeit: --
1582 #=stripHNE(#);
1583 //----------------- Multiplizitaetensequenz eines Zweiges --------------------
1584 if (typeof(#[1])=="matrix") {
1585   if (#[3]==-1) {
1586     "An error has occurred in develop, so there is no HNE.";
1587   }
1588   else {
1589     "The sequence of multiplicities is  ",multiplicities(#);
1590 }}
1591 //---------------------------- mehrere Zweige --------------------------------
1592 else {
1593   list multips=multsequence(#);
1594   int i,j,k,l;
1595   string output;
1596   for (i=1; i<=nrows(multips[1]); i++) {
1597     output="[";
1598     k=1;
1599     for (l=1; k<=ncols(multips[1]); l++) {
1600       output=output+"(";
1601       for (j=1; j<=multips[2][i,l]; j++) {
1602         output=output+string(multips[1][i,k]);
1603         k++;
1604         if (j<multips[2][i,l]) { output=output+","; }
1605       }
1606       output=output+")";
1607       if ((k-1) < ncols(multips[1])) { output=output+","; }
1608      }
1609     output=output+"]";
1610     if (i<nrows(multips[1])) { output=output+","; }
1611     output;
1612   }
1613 }
1614} // example multsequence; geht wegen echo nicht (muesste auf 3 gesetzt werden)
1615example
1616{
1617  // -------- prepare for example ---------
1618  if (nameof(basering)=="HNEring") {
1619   def rettering=HNEring;
1620   kill HNEring;
1621  }
1622  // ------ the example starts here -------
1623  "EXAMPLE:"; echo = 2;
1624  ring r=0,(x,y),dp;
1625  list hne=reddevelop((x6-y10)*(x+y2-y3)*(x+y2+y3));
1626
1627  displayMultsequence(hne[1]);
1628  displayMultsequence(hne);
1629  kill HNEring,r;
1630  echo = 0;
1631  // --- restore HNEring if previously defined ---
1632  if (defined(rettering)) {
1633   setring rettering;
1634   def HNEring=rettering;
1635   export HNEring;
1636  }
1637}
1638///////////////////////////////////////////////////////////////////////////////
1639
1640proc separateHNE (list hn1,list hn2)
1641"USAGE:    separateHNE(hne1,hne2);  list hne1,hne2: output of develop
1642RETURN:   number of quadratic transformations needed to separate both curves
1643SEE ALSO: develop, reddevelop, multsequence, displayMultsequence
1644EXAMPLE:  example separateHNE;  shows an example
1645"
1646{
1647 int i,j,s,unterschied,separated;
1648 matrix a1=hn1[1];
1649 matrix a2=hn2[1];
1650 intvec h1=hn1[2];
1651 intvec h2=hn2[2];
1652 if (hn1[3]!=hn2[3]) {
1653 //-- die jeweils erste Zeile von hn1,hn2 gehoert zu verschiedenen Parametern -
1654 //---------------- d.h. beide Kurven schneiden sich transversal --------------
1655   separated=1;
1656 }
1657 else {
1658 //--------- die jeweils erste Zeile gehoert zum gleichen Parameter -----------
1659   unterschied=0;
1660   for (s=1; (h1[s]==h2[s]) && (s<size(h1)) && (s<size(h2))
1661              && (unterschied==0); s++) {
1662     for (i=1; (a1[s,i]==a2[s,i]) && (i<=h1[s]); i++) {;}
1663     if (i<=h1[s]) {
1664       unterschied=1;
1665       s--;                    // um s++ am Schleifenende wieder auszugleichen
1666     }
1667   }
1668   if (unterschied==0) {
1669     if ((s<size(h1)) && (s<size(h2))) {
1670       for (i=1; (a1[s,i]==a2[s,i]) && (i<=h1[s]) && (i<=h2[s]); i++) {;}
1671     }
1672     else {
1673 //-------------- Sonderfall: Unterschied in letzter Zeile suchen -------------
1674 // Beachte: Es koennen undefinierte Stellen auftreten, bei abbrechender HNE
1675 // muss die Ende-Markierung weg, h_[r] ist unendlich, die Matrix muss mit
1676 // Nullen fortgesetzt gedacht werden
1677 //----------------------------------------------------------------------------
1678       if (ncols(a1)>ncols(a2)) { j=ncols(a1); }
1679       else                     { j=ncols(a2); }
1680       unterschied=0;
1681       if ((h1[s]>0) && (s==size(h1))) {
1682         a1[s,h1[s]+1]=0;
1683         if (ncols(a1)<=ncols(a2)) { unterschied=1; }
1684       }
1685       if ((h2[s]>0) && (s==size(h2))) {
1686         a2[s,h2[s]+1]=0;
1687         if (ncols(a2)<=ncols(a1)) { unterschied=1; }
1688       }
1689       if (unterschied==1) {                   // mind. eine HNE war endlich
1690         matrix ma1[1][j]=a1[s,1..ncols(a1)];  // und bedarf der Fortsetzung
1691         matrix ma2[1][j]=a2[s,1..ncols(a2)];  // mit Nullen
1692       }
1693       else {
1694         if (ncols(a1)>ncols(a2)) { j=ncols(a2); }
1695         else                     { j=ncols(a1); }
1696         matrix ma1[1][j]=a1[s,1..j];          // Beschr. auf vergleichbaren
1697         matrix ma2[1][j]=a2[s,1..j];          // Teil (der evtl. y's enth.)
1698       }
1699       for (i=1; (ma1[1,i]==ma2[1,i]) && (i<j) && (ma1[1,i]!=var(2)); i++) {;}
1700       if (ma1[1,i]==ma2[1,i]) {
1701         "//** The two HNE's are identical!";
1702         "//** You have either tried to compare a branch with itself,";
1703         "//** or the two branches have been developed separately.";
1704         "//   In the latter case use `extdevelop' to extend the HNE's until",
1705         "they differ.";
1706         return(-1);
1707       }
1708       if ((ma1[1,i]==var(2)) || (ma2[1,i]==var(2))) {
1709         "//** The two HNE's are (so far) identical. This is because they",
1710         "have been";
1711         "//** computed separately. I need more data; use `extdevelop' to",
1712         "extend them,";
1713         if (ma1[1,i]==var(2)) {"//** at least the first one.";}
1714         else                  {"//** at least the second one.";}
1715         return(-1);
1716       }
1717     }
1718   }
1719   separated=i;
1720   for (j=1; j<s; j++) { separated=separated+h1[j]; }
1721 }
1722 return(separated);
1723}
1724example
1725{ "EXAMPLE:"; echo = 2;
1726  int p=printlevel; printlevel=-1;
1727  ring r=0,(x,y),dp;
1728  list hne1=develop(x);
1729  list hne2=develop(x+y);
1730  list hne3=develop(x+y2);
1731  separateHNE(hne1,hne2);  // two transversal lines
1732  separateHNE(hne1,hne3);  // one quadratic transform. gives 1st example
1733  printlevel=p;
1734}
1735///////////////////////////////////////////////////////////////////////////////
1736
1737proc displayHNE(list ldev,list #)
1738"USAGE:   displayHNE(ldev,[,n]); ldev=list (the output of develop(f) or
1739          reddevelop(f)), n=int
1740RETURN:  - if only one argument is given, no return value, but
1741         display an ideal HNE of the following form:
1742     @example
1743     HNE[1]=-y+[]*z(0)^1+[]*z(0)^2+...+z(0)^<>*z(1)
1744     HNE[2]=-x+          []*z(1)^2+...+z(1)^<>*z(2)
1745     HNE[3]=             []*z(2)^2+...+z(2)^<>*z(3)
1746     .......             ..........................
1747     HNE[r+1]=           []*z(r)^2+[]*z(r)^3+......
1748     @end example
1749     where x,y are the indeterminates of the basering. The values of @code{[]}
1750     are the coefficients of the Hamburger-Noether matrix, the values of
1751     @code{<>} are represented in the HN-matrix as `x'.
1752     @*  The 1st line (@code{HNE[1]}) means that
1753     @math{y=}@code{[]}@math{*z(0)^1+...},
1754       the 2nd line (@code{HNE[2]}) means that
1755     @math{x=}@code{[]}@math{*z(1)^2+...},
1756     so you can see which indeterminate corresponds to which line
1757     (it's also possible that x corresponds to the 1st line and y to the 2nd).
1758     @*  - if a second argument is given, create and export a new ring with
1759         name `displayring' containing an ideal `HNE' as described above.
1760
1761     If ldev contains the output of @code{reddevelop}(f), @code{displayHNE}
1762     shows the HNE's of all branches of f in the form described above.
1763     The optional parameter is then ignored.
1764
1765SEE ALSO: develop, reddevelop
1766EXAMPLE: example displayHNE; shows an example
1767"
1768{
1769 if ((typeof(ldev[1])=="list") || (typeof(ldev[1])=="none")) {
1770   for (int i=1; i<=size(ldev); i++) {
1771     "// Hamburger-Noether development of branch nr."+string(i)+":";
1772     displayHNE(ldev[i]);"";
1773   }
1774   return();
1775 }
1776 //--------------------- Initialisierungen und Ringwechsel --------------------
1777 matrix m=ldev[1];
1778 intvec v=ldev[2];
1779 int switch=ldev[3];
1780 if (switch==-1) {
1781   "An error has occurred in develop, so there is no HNE.";
1782   return(ideal(0));
1783 }
1784 def altring=basering;
1785 if (parstr(basering)!="") {
1786   if (charstr(basering)!=string(char(basering))+","+parstr(basering)) {
1787     execute
1788      ("ring dazu=("+charstr(basering)+"),z(0.."+string(size(v)-1)+"),ls;");
1789   }
1790   else { ring dazu=char(altring),z(0..size(v)-1),ls; }
1791 }
1792 else   { ring dazu=char(altring),z(0..size(v)-1),ls; }
1793 def displayring=dazu+altring;
1794 setring displayring;
1795 if (size(#) != 0) {
1796    export displayring;
1797  }
1798 map holematrix=altring,0;        // mappt nur die Monome vom Grad Null
1799 matrix m=holematrix(m);
1800 //--------------------- Erzeuge Matrix n mit n[i,j]=z(j-1)^i -----------------
1801 int i;
1802 matrix n[ncols(m)][nrows(m)];
1803 for (int j=1; j<=nrows(m); j++) {
1804    for (i=1; i<=ncols(m); i++) { n[i,j]=z(j-1)^i; }
1805 }
1806 matrix displaymat=m*n;
1807 ideal HNE;
1808 for (i=1; i<nrows(m); i++) { HNE[i]=displaymat[i,i]+z(i)*z(i-1)^v[i]; }
1809 HNE[nrows(m)]=displaymat[nrows(m),nrows(m)];
1810 if (nrows(m)<2) { HNE[2]=z(0); }
1811 if (switch==0) {
1812    HNE[1] = HNE[1]-var(size(v)+2);
1813    HNE[2] = HNE[2]-var(size(v)+1);
1814 }
1815 else {
1816    HNE[1] = HNE[1]-var(size(v)+1);
1817    HNE[2] = HNE[2]-var(size(v)+2);
1818 }
1819if (size(#) == 0) {
1820   HNE;
1821   return();
1822 }
1823if (size(#) != 0) {
1824   "// basering is now 'displayring' containing ideal 'HNE'";
1825   keepring(displayring);
1826   export(HNE);
1827   return(HNE);
1828 }
1829}
1830example
1831{ "EXAMPLE:"; echo = 2;
1832  ring r=0,(x,y),dp;
1833  poly f=x3+2xy2+y2;
1834  list hn=develop(f);
1835  displayHNE(hn);
1836}
1837///////////////////////////////////////////////////////////////////////////////
1838//                      procedures for reducible curves                      //
1839///////////////////////////////////////////////////////////////////////////////
1840
1841// proc newtonhoehne (poly f)
1842// USAGE:   newtonhoehne(f);   f poly
1843// ASSUME:  basering = ...,(x,y),ds  or ls
1844// RETURN:  list of intvec(x,y) of coordinates of the newtonpolygon of f
1845// NOTE:    This proc is only available in versions of Singular that know the
1846//         command  system("newton",f);  f poly
1847// {
1848// intvec nm = getnm(f);
1849//  if ((nm[1]>0) && (nm[2]>0)) { f=jet(f,nm[1]*nm[2],nm); }
1850//  list erg=system("newton",f);
1851//  int i; list Ausgabe;
1852//  for (i=1; i<=size(erg); i++) { Ausgabe[i]=leadexp(erg[i]); }
1853// return(Ausgabe);
1854// }
1855///////////////////////////////////////////////////////////////////////////////
1856
1857proc newtonpoly (poly f)
1858"USAGE:   newtonpoly(f);   f poly
1859RETURN:  list of intvec(x,y) of coordinates of the Newton polygon of f
1860ASSUME: For performance reasons, newtonpoly assumes that
1861      - the basering has ordering `ls'
1862      - f(x,0) != 0 != f(0,y), f(0,0) = 0
1863EXAMPLE: example newtonpoly;  shows an example
1864"
1865{
1866 intvec A=(0,ord(subst(f,var(1),0)));
1867 intvec B=(ord(subst(f,var(2),0)),0);
1868 intvec C,H; list L;
1869 int abbruch,i;
1870 poly hilf;
1871
1872 L[1]=A;
1873 //-------- wirf alle Monome auf oder oberhalb der Geraden AB raus: -----------
1874 f=jet(f,A[2]*B[1]-1,intvec(A[2],B[1]));
1875 map xytausch=basering,var(2),var(1);
1876 for (i=2; f!=0; i++) {
1877   abbruch=0;
1878   while (abbruch==0) {
1879 // finde den Punkt aus {verbliebene Pkte (a,b) mit a minimal} mit b minimal: -
1880
1881     C=leadexp(f);           // Ordnung ls ist wesentlich!
1882
1883     if (jet(f,A[2]*C[1]-A[1]*C[2]-1,intvec(A[2]-C[2],C[1]-A[1]))==0)
1884       { abbruch=1; }        // keine Monome unterhalb der Geraden AC
1885
1886 // ----- alle Monome auf der Parallelen zur y-Achse durch C wegwerfen: -------
1887 // ------------------ (links von C gibt es sowieso keine mehr) ---------------
1888     else { f=jet(f,-C[1]-1,intvec(-1,0)); }
1889   }
1890 //- finde alle Monome auf der Geraden durch A und C (unterhalb gibt's keine) -
1891   hilf=jet(f,A[2]*C[1]-A[1]*C[2],intvec(A[2]-C[2],C[1]-A[1]));
1892
1893   H=leadexp(xytausch(hilf));
1894   A=H[2],H[1];
1895
1896 // die Alternative waere ein Ringwechsel nach ..,(y,x),ds gewesen
1897 // A_neu ist der naechste Eckpunkt (unterster Punkt auf Geraden durch A,C)
1898
1899   L[i]=A;
1900 //----------------- alle Monome auf oder unterhalb AB raus -------------------
1901   f=jet(f,A[2]*B[1]-1,intvec(A[2],B[1]-A[1]));
1902 }
1903 L[i]=B;
1904 return(L);
1905}
1906example
1907{ "EXAMPLE:";
1908  ring @exring_Newt=0,(x,y),ls;
1909  export @exring_Newt;
1910  "  ring exring=0,(x,y),ls;";
1911  echo = 2;
1912  poly f=x5+2x3y-x2y2+3xy5+y6-y7;
1913  newtonpoly(f);
1914  echo = 0;
1915  kill @exring_Newt;
1916}
1917///////////////////////////////////////////////////////////////////////////////
1918
1919proc charPoly(poly f, int M, int N)
1920"USAGE:  charPoly(f,M,N);  f bivariate poly,  M,N int: length and height
1921                          of Newton polygon of f, which has to be only one line
1922RETURN:  the characteristic polynomial of f
1923EXAMPLE: example charPoly;  shows an example
1924"
1925{
1926 poly charp;
1927 int Np=N/ gcd(M,N);
1928 f=subst(f,var(1),1);
1929 for(charp=0; f<>0; f=f-lead(f))
1930  { charp=charp+leadcoef(f)*var(2)^(leadexp(f)[2]/ Np);}
1931 return(charp);
1932}
1933example
1934{ "EXAMPLE:"; echo = 2;
1935  ring exring=0,(x,y),dp;
1936  charPoly(y4+2y3x2-yx6+x8,8,4);
1937  charPoly(y6+3y3x2-x4,4,6);
1938}
1939///////////////////////////////////////////////////////////////////////////////
1940
1941proc find_in_list(list L,int p)
1942"USAGE:   find_in_list(L,p); L: list of intvec(x,y)
1943         (sorted in y: L[1][2]>=L[2][2]), int p >= 0
1944RETURN:  int i: L[i][2]=p if existent; otherwise i with L[i][2]<p if existent;
1945         otherwise i = size(L)+1;
1946EXAMPLE: example find_in_list;  shows an example
1947"
1948{
1949 int i;
1950 L[size(L)+1]=intvec(0,-1);          // falls p nicht in L[.][2] vorkommt
1951 for (i=1; L[i][2]>p; i++) {;}
1952 return(i);
1953}
1954example
1955{ "EXAMPLE:"; echo = 2;
1956  list L = intvec(0,4), intvec(1,2), intvec(2,1), intvec(4,0);
1957  find_in_list(L,1);
1958  L[find_in_list(L,2)];
1959}
1960///////////////////////////////////////////////////////////////////////////////
1961
1962proc get_last_divisor(int M, int N)
1963"USAGE:   get_last_divisor(M,N); int M,N
1964RETURN:  int Q: M=q1*N+r1, N=q2*r1+r2, ..., ri=Q*r(i+1) (Euclidean alg.)
1965EXAMPLE: example get_last_divisor; shows an example
1966"
1967{
1968 int R=M%N; int Q=M / N;
1969 while (R!=0) {M=N; N=R; R=M%N; Q=M / N;}
1970 return(Q)
1971}
1972example
1973{ "EXAMPLE"; echo = 2;
1974  ring r=0,(x,y),dp;
1975  get_last_divisor(12,10);
1976}
1977///////////////////////////////////////////////////////////////////////////////
1978proc redleit (poly f,intvec S, intvec E)
1979"USAGE:   redleit(f,S,E);  f poly, S,E intvec(x,y)
1980         S,E are two different points on a line in the Newton diagram of f
1981RETURN:  poly g: all monomials of f which lie on or below that line
1982NOTE:    The main purpose is that if the line defined by S and E is part of the
1983         Newton polygon, the result is the quasihomogeneous leading form of f
1984         wrt. that line.
1985SEE ALSO: newtonpoly
1986EXAMPLE: example redleit;  shows an example
1987"
1988{
1989 if (E[1]<S[1]) { intvec H=E; E=S; S=H; } // S,E verkehrt herum eingegeben
1990 return(jet(f,E[1]*S[2]-E[2]*S[1],intvec(S[2]-E[2],E[1]-S[1])));
1991}
1992example
1993{ "EXAMPLE"; echo = 2;
1994  ring exring=0,(x,y),dp;
1995  redleit(y6+xy4-2x3y2+x4y+x6,intvec(3,2),intvec(4,1));
1996}
1997///////////////////////////////////////////////////////////////////////////////
1998
1999
2000proc extdevelop (list l, int Exaktheit)
2001"USAGE:   extdevelop(l,n);
2002         list l (matrix m, intvec v, int s, poly g[,int b]), int n
2003 @*      takes the output l of develop(f) ( or extdevelop(L,N),
2004         or one entry of the output of reddevelop(f))  and
2005RETURN:  an extension of the Hamburger-Noether development of f in the same
2006         form as l (i.e. list(matrix, intvec, int, poly) ).
2007         The new HN-matrix will have at least n columns
2008         (if the HNE isn't finite).
2009         Thus if f is irreducible, @code{extdevelop}(@code{develop}(f),n);
2010         (in most cases) will produce the same result as @code{develop}(f,n).
2011         Type `help develop;'  for more details.
2012NOTE:    If the matrix m of l has N columns, the exactness of
2013         @code{param}(@code{extdevelop}(l,n))  will be increased by at least
2014         (n-N) more significant monomials compared with @code{param}(l).
2015SEE ALSO: develop, reddevelop, param
2016EXAMPLE: example extdevelop;  shows an example
2017"
2018{
2019 //------------ Initialisierungen und Abfangen unzulaessiger Aufrufe ----------
2020 matrix m=l[1];
2021 intvec v=l[2];
2022 int switch=l[3];
2023 if (nvars(basering) < 2) {
2024   " Sorry. I need two variables in the ring.";
2025   return(list(matrix(maxideal(1)[1]),intvec(0),-1,poly(0)));}
2026 if (switch==-1) {
2027   "An error has occurred in develop, so there is no HNE and no extension.";
2028   return(l);
2029 }
2030 poly f=l[4];
2031 if (f==0) {
2032   " No extension is possible";
2033   return(l);
2034 }
2035 int Q=v[size(v)];
2036 if (Q>0) {
2037   " The HNE was already exact";
2038   return(l);
2039 }
2040 else {
2041   if (Q==-1) { Q=ncols(m); }
2042   else { Q=-Q-1; }
2043 }
2044 int zeile=nrows(m);
2045 int spalten,i,M;
2046 ideal lastrow=m[zeile,1..Q];
2047 int ringwechsel=(varstr(basering)!="x,y") or (ordstr(basering)!="ls(2),C");
2048
2049 //------------------------- Ringwechsel, falls noetig ------------------------
2050 if (ringwechsel) {
2051  def altring = basering;
2052  int p = char(basering);
2053  if (charstr(basering)!=string(p)) {
2054     string tststr=charstr(basering);
2055     tststr=tststr[1..find(tststr,",")-1];     //-> "p^k" bzw. "p"
2056     if (tststr==string(p)) {
2057       if (size(parstr(basering))>1) {         // ring (p,a,..),...
2058        execute("ring extdguenstig=("+charstr(basering)+"),(x,y),ls;");
2059       }
2060       else {                                  // ring (p,a),...
2061        string mipl=string(minpoly);
2062        ring extdguenstig=(p,`parstr(basering)`),(x,y),ls;
2063        if (mipl!="0") { execute("minpoly="+mipl+";"); }
2064       }
2065     }
2066     else {
2067       execute("ring extdguenstig=("+charstr(basering)+"),(x,y),ls;");
2068     }
2069  }
2070  else {                               // charstr(basering)== p : no parameter
2071     ring extdguenstig=p,(x,y),ls;
2072  }
2073  export extdguenstig;
2074  map hole=altring,x,y;
2075 //----- map kann sehr zeitaufwendig sein, daher Vermeidung, wo moeglich: -----
2076  if (nvars(altring)==2) { poly f=fetch(altring,f); }
2077  else                   { poly f=hole(f);          }
2078  ideal a=hole(lastrow);
2079 }
2080 else { ideal a=lastrow; }
2081 list Newton=newtonpoly(f);
2082 int M1=Newton[size(Newton)-1][1];     // konstant
2083 number delta;
2084 if (Newton[size(Newton)-1][2]!=1) {
2085    " *** The transformed polynomial was not valid!!";}
2086 else {
2087 //--------------------- Fortsetzung der HNE ----------------------------------
2088  while (Q<Exaktheit) {
2089    M=ord(subst(f,y,0));
2090    Q=M-M1;
2091 //------ quasihomogene Leitform ist c*x^M1*y+d*x^(M1+Q) => delta=-d/c: -------
2092    delta=-koeff(f,M,0)/koeff(f,M1,1);
2093    a[Q]=delta;
2094    if ((voice==2) && (printlevel > -1))
2095     { "a("+string(zeile-1)+","+string(Q)+") =",delta; }
2096    if (Q<Exaktheit) {
2097     f=T1_Transform(f,delta,Q);
2098     if (defined(HNDebugOn)) { "transformed polynomial:",f; }
2099     if (subst(f,y,0)==0) {
2100       if ((voice==2) && (printlevel > -1)) { "The HNE is finite!"; }
2101       a[Q+1]=x; Exaktheit=Q;
2102       f=0;                        // Speicherersparnis: f nicht mehr gebraucht
2103     }
2104    }
2105  }
2106 }
2107 //------- Wechsel in alten Ring, Zusammensetzung alte HNE + Erweiterung ------
2108 if (ringwechsel) {
2109  setring altring;
2110  map zurueck=extdguenstig,var(1),var(2);
2111  if (nvars(altring)==2) { f=fetch(extdguenstig,f); }
2112  else                   { f=zurueck(f);            }
2113  lastrow=zurueck(a);
2114 }
2115 else { lastrow=a; }
2116 if (ncols(lastrow)>ncols(m)) { spalten=ncols(lastrow); }
2117 else { spalten=ncols(m); }
2118 matrix mneu[zeile][spalten];
2119 for (i=1; i<nrows(m); i++) {
2120  mneu[i,1..ncols(m)]=m[i,1..ncols(m)];
2121 }
2122 mneu[zeile,1..ncols(lastrow)]=lastrow;
2123 if (lastrow[ncols(lastrow)]!=var(1)) {
2124  if (ncols(lastrow)==spalten) { v[zeile]=-1; }  // keine undefinierten Stellen
2125  else {
2126   v[zeile]=-Q-1;
2127   for (i=ncols(lastrow)+1; i<=spalten; i++) {
2128    mneu[zeile,i]=var(2);           // fuelle nicht def. Stellen der Matrix auf
2129 }}}
2130 else { v[zeile]=Q; }               // HNE war exakt
2131 if (ringwechsel)
2132 {
2133   if(system("with","Namespaces")) { kill Top::extdguenstig; }
2134   kill extdguenstig;
2135 }
2136
2137 return(list(mneu,v,switch,f));
2138}
2139example
2140{
2141  // -------- prepare for example ---------
2142  if (nameof(basering)=="HNEring") {
2143   def rettering=HNEring;
2144   kill HNEring;
2145  }
2146  // ------ the example starts here -------
2147  "EXAMPLE:"; echo = 2;
2148  ring exring=0,(x,y),dp;
2149  list hne=reddevelop(x14-3y2x11-y3x10-y2x9+3y4x8+y5x7+3y4x6+x5*(-y6+y5)
2150                      -3y6x3-y7x2+y8);
2151  print(hne[1][1]); // finite HNE
2152  print(extdevelop(hne[1],5)[1]);
2153  // ------------------------------------------
2154  print(hne[2][1]); // HNE that can be extended
2155  list ehne=extdevelop(hne[2],5);
2156  print(ehne[1]); // new HN-matrix has 5 columns
2157  param(hne[2]);
2158  param(ehne);
2159  kill HNEring,exring;
2160  echo = 0;
2161  // --- restore HNEring if previously defined ---
2162  if (defined(rettering)) {
2163   setring rettering;
2164   def HNEring=rettering;
2165   export HNEring;
2166  }
2167}
2168///////////////////////////////////////////////////////////////////////////////
2169
2170proc stripHNE (list l)
2171"USAGE:   stripHNE(l);    takes the output both of develop(f) and reddevelop(f)
2172 @*        ( list l (matrix m, intvec v, int s[,poly g,...])
2173             or list of lists in the form l )
2174RETURN:  a list in the same format as l, but all polynomials g are set to zero
2175NOTE:    The purpose of this procedure is to remove huge amounts of data
2176         no longer needed. It is useful, if one or more of the polynomials
2177         in l consumes much memory. It is still possible to compute invariants,
2178         parametrizations etc. with the stripped HNE(s), but it is not possible
2179         to use extdevelop with them.
2180SEE ALSO: develop, reddevelop, extdevelop
2181EXAMPLE: example stripHNE;  shows an example
2182"
2183{
2184 list h;
2185 if (typeof(l[1])=="matrix") { l[4]=poly(0); }
2186 else {
2187  for (int i=1; i<=size(l); i++) {
2188    h=l[i];
2189    h[4]=poly(0);
2190    l[i]=h;
2191  }
2192 }
2193 return(l);
2194}
2195example
2196{ "EXAMPLE:"; echo = 2;
2197  ring r=0,(x,y),dp;
2198  list hne=develop(x2+y3+y4);
2199  hne;
2200  stripHNE(hne);
2201}
2202///////////////////////////////////////////////////////////////////////////////
2203static proc extractHNEs(list HNEs, int transvers)
2204"USAGE:  extractHNEs(HNEs,transvers);  list HNEs (output from HN),
2205        int transvers: 1 if x,y were exchanged, 0 else
2206RETURN: list of Hamburger-Noether-Extensions in the form of reddevelop
2207NOTE:   This procedure is only for internal purpose; examples don't make sense
2208"
2209{
2210 int i,maxspalte,hspalte,hnezaehler;
2211 list HNEaktu,Ergebnis;
2212 for (hnezaehler=1; hnezaehler<=size(HNEs); hnezaehler++) {
2213  maxspalte=0;
2214  HNEaktu=HNEs[hnezaehler];
2215  if (defined(HNDebugOn)) {"To process:";HNEaktu;}
2216  if (size(HNEaktu)!=size(HNEaktu[1])+2) {
2217     "The ideals and the hqs in HNEs[",hnezaehler,"] don't match!!";
2218     HNEs[hnezaehler];
2219  }
2220 //------------ ermittle  maximale Anzahl benoetigter Spalten: ----------------
2221  for (i=2; i<size(HNEaktu); i++) {
2222    hspalte=ncols(HNEaktu[i]);
2223    maxspalte=maxspalte*(hspalte < maxspalte)+hspalte*(hspalte >= maxspalte);
2224  }
2225 //------------- schreibe Ausgabe fuer hnezaehler-ten Zweig: ------------------
2226  matrix ma[size(HNEaktu)-2][maxspalte];
2227  for (i=1; i<=(size(HNEaktu)-2); i++) {
2228    if (ncols(HNEaktu[i+1]) > 1) {
2229      ma[i,1..ncols(HNEaktu[i+1])]=HNEaktu[i+1]; }
2230    else { ma[i,1]=HNEaktu[i+1][1];}
2231  }
2232  Ergebnis[hnezaehler]=list(ma,HNEaktu[1],transvers,HNEaktu[size(HNEaktu)]);
2233  kill ma;
2234 }
2235 return(Ergebnis);
2236}
2237///////////////////////////////////////////////////////////////////////////////
2238
2239proc factorfirst(poly f, int M, int N)
2240"USAGE : factorfirst(f,M,N); f poly, M,N int
2241RETURN: number d: f=c*(y^(N/e) - d*x^(M/e))^e with e=gcd(M,N), number c fitting
2242        0 if d does not exist
2243EXAMPLE: example factorfirst;  shows an example
2244"
2245{
2246 number c = koeff(f,0,N);
2247 number delta;
2248 int eps,l;
2249 int p=char(basering);
2250 string ringchar=charstr(basering);
2251
2252 if (c == 0) {"Something has gone wrong! I didn't get N correctly!"; exit;}
2253 int e = gcd(M,N);
2254
2255 if (p==0) { delta = koeff(f,M/ e,N - N/ e) / (-1*e*c); }
2256 else {
2257   if (e%p != 0) { delta = koeff(f,M/ e,N - N/ e) / (-1*e*c); }
2258   else {
2259     eps = e;
2260     for (l = 0; eps%p == 0; l=l+1) { eps=eps/ p;}
2261     if (defined(HNDebugOn)) {e," -> ",eps,"*",p,"^",l;}
2262     delta = koeff(f,(M/ e)*p^l,(N/ e)*p^l*(eps-1)) / (-1*eps*c);
2263
2264     if ((charstr(basering) != string(p)) and (delta != 0)) {
2265 //------ coefficient field is not Z/pZ => (p^l)th root is not identity -------
2266       delta=0;
2267       if (defined(HNDebugOn)) {
2268         "trivial factorization not implemented for",
2269         "parameters---I've to use 'factorize'";
2270       }
2271     }
2272   }
2273 }
2274 if (defined(HNDebugOn)) {"quasihomogeneous leading form:",f," = ",c,
2275        "* (y^"+string(N/ e),"-",delta,"* x^"+string(M/ e)+")^",e," ?";}
2276 if (f != c*(var(2)^(N/ e) - delta*var(1)^(M/ e))^e) {return(0);}
2277 else {return(delta);}
2278}
2279example
2280{ "EXAMPLE:"; echo = 2;
2281  ring exring=7,(x,y),dp;
2282  factorfirst(2*(y3-3x4)^5,20,15);
2283  factorfirst(x14+y7,14,7);
2284  factorfirst(x14+x8y3+y7,14,7);
2285}
2286///////////////////////////////////////////////////////////////////////////////
2287
2288proc HNdevelop (poly f)
2289"USAGE:   HNdevelop(f); f poly
2290RETURN:  Hamburger-Noether development of f:
2291         A list of lists in the form of develop(f)
2292         (matrix,intvec,int,poly -- the last int indicating irreducibility is
2293         omitted); each entry contains the data for one of the branches of f.
2294         For more details type `help develop;'
2295CREATE:  a ring with name `HNEring', variables `x,y' and ordering `ls' over
2296         a field extension of the current basering's ground field.
2297         As the Hamburger-Noether development normally does not exist
2298         in the originally given basering, @code{HNdevelop} always defines
2299         HNEring and changes to it. The field extension is chosen minimal.
2300NOTE:    @code{HNdevelop} decides which procedure (@code{develop} or
2301         @code{reddevelop}) applies best to the given problem and calls it.
2302SEE ALSO: develop, reddevelop, extdevelop
2303EXAMPLE: example HNdevelop;  shows an example
2304"
2305{
2306 int irred=0;
2307 //--------- Falls Ring (p^k,a),...: Wechsel in (p,a),... + minpoly -----------
2308 if ((find(charstr(basering),string(char(basering)))!=1) &&
2309     (charstr(basering)<>"real")) {
2310   string strmip=string(minpoly);
2311   string strf=string(f);
2312   execute("ring tempr=("+string(char(basering))+","+parstr(basering)+"),("
2313           +varstr(basering)+"),dp;");
2314   execute("minpoly="+strmip+";");
2315   execute("poly f="+strf+";");
2316   list hne=reddevelop(f);
2317   if ((voice==2) && (printlevel > -1)) {
2318     "// Attention: The parameter",par(1),"has changed its meaning!";
2319     "// It need no longer be a generator of the cyclic group of unities!";
2320   }
2321 }
2322 else {
2323 //--- Falls Ring (0,a),... + minpoly : solange factorize nicht in Singular ---
2324 //------- implementiert ist, develop aufrufen (kann spaeter entfallen) -------
2325   if ((char(basering)==0) && (npars(basering)==1)) {
2326     if (string(minpoly)<>"0") { irred=1; }
2327   }
2328 //------------------ Aufruf der geeigneten Prozedur --------------------------
2329   if (irred==0) {
2330     list hne=pre_HN(f,0);       // = reddevelop(f);
2331     dbprint(printlevel+1,
2332        "// result: "+string(size(hne))+" branch(es) successfully computed,",
2333        "//         basering has changed to HNEring");
2334   }
2335   else {
2336     def altring=basering;
2337     string strmip=string(minpoly);
2338     ring HNEring=(char(altring),`parstr(altring)`),(x,y),ls;
2339     execute("minpoly="+strmip+";");
2340     export HNEring;
2341     poly f=fetch(altring,f);
2342     list hn=develop(f,-1);
2343     list hne;
2344     if (hn[3] <> -1) {
2345       hne[1]=list(hn[1],hn[2],hn[3],hn[4]);
2346       if (hn[5] <> 1) {
2347   " ** WARNING : The curve is reducible, but only one branch could be found!";
2348       }
2349     }
2350     else { " ** Sorry -- could not find a HNE."; }
2351     dbprint(printlevel+1,"// note: basering has changed to HNEring");
2352   }
2353 }
2354 keepring basering;
2355 return(hne);
2356}
2357example
2358{
2359  // -------- prepare for example ---------
2360  if (nameof(basering)=="HNEring") {
2361   def rettering=HNEring;
2362   kill HNEring;
2363  }
2364  // ------ the example starts here -------
2365  "EXAMPLE:"; echo = 2;
2366  ring r=0,(x,y),dp;
2367  list hne=HNdevelop(x4-y6);
2368  nameof(basering);
2369  size(hne);           // i.e. x4-y6 has two branches
2370  print(hne[1][1]);    // HN-matrix of 1st branch
2371  param(hne[1]);
2372  param(hne[2]);
2373  displayInvariants(hne);
2374  kill HNEring,r;
2375  echo = 0;
2376  // --- restore HNEring if previously defined ---
2377  if (defined(rettering)) {
2378   setring rettering;
2379   def HNEring=rettering;
2380   export HNEring;
2381  }
2382}
2383///////////////////////////////////////////////////////////////////////////////
2384
2385proc reddevelop (poly f)
2386"USAGE:   reddevelop(f); f poly
2387RETURN:  Hamburger-Noether development of f:
2388         A list of lists in the form of develop(f)
2389         (matrix,intvec,int,poly -- the last int indicating irreducibility is
2390         omitted); each entry contains the data for one of the branches of f.
2391         For more details type `help develop;'
2392CREATE:  a ring with name `HNEring', variables `x,y' and ordering `ls' over
2393         a field extension of the current basering's ground field.
2394         As the Hamburger-Noether development of a reducible curve normally
2395         does not exist in the given basering, @code{reddevelop} always defines
2396         HNEring and changes to it. The field extension is chosen minimal.
2397SEE ALSO: develop, extdevelop, displayHNE
2398EXAMPLE: example reddevelop;  shows an example
2399"
2400{
2401 list Ergebnis=pre_HN(f,0);
2402 if (size(Ergebnis)>0) {     // otherwise an error may have occurred
2403  dbprint(printlevel+1,
2404   "// result: "+string(size(Ergebnis))+" branch(es) successfully computed,",
2405   "//         basering has changed to HNEring");
2406 }
2407 keepring basering;
2408 return(Ergebnis);
2409}
2410example
2411{
2412  // -------- prepare for example ---------
2413  if (nameof(basering)=="HNEring")
2414  {
2415   def rettering=HNEring;
2416   kill HNEring;
2417  }
2418  // ------ the example starts here -------
2419  "EXAMPLE:"; echo = 2;
2420  ring r=0,(x,y),dp;
2421  list hne=reddevelop(x4-y6);
2422  size(hne);           // i.e. x4-y6 has two branches
2423  print(hne[1][1]);    // HN-matrix of 1st branch
2424  param(hne[1]);
2425  param(hne[2]);
2426  displayInvariants(hne);
2427  kill HNEring,r;
2428  // ----------------- a more interesting example: --------------------
2429  ring r = 32003,(x,y),dp;
2430  poly f = x25+x24-4x23-1x22y+4x22+8x21y-2x21-12x20y-4x19y2+4x20+10x19y
2431          +12x18y2-24x18y-20x17y2-4x16y3+x18+60x16y2+20x15y3-9x16y
2432          -80x14y3-10x13y4+36x14y2+60x12y4+2x11y5-84x12y3-24x10y5
2433          +126x10y4+4x8y6-126x8y5+84x6y6-36x4y7+9x2y8-1y9;
2434  list hne=reddevelop(f);
2435  size(hne);
2436  print(hne[1][1]);
2437  print(hne[4][1]);
2438  // a ring change was necessary, a is a parameter
2439  HNEring;
2440  kill HNEring,r;
2441  echo = 0;
2442  // --- restore HNEring if previously defined ---
2443  if (defined(rettering)) {
2444   setring rettering;
2445   def HNEring=rettering;
2446   export HNEring;
2447  }
2448}
2449///////////////////////////////////////////////////////////////////////////////
2450
2451static proc pre_HN (poly f, int essential)
2452"NOTE: This procedure is only for internal use, it is called via
2453      reddevelop or essdevelop"
2454{
2455 def altring = basering;
2456 int p = char(basering);                 // Ringcharakteristik
2457
2458 //-------------------- Tests auf Zulaessigkeit von basering ------------------
2459 if (charstr(basering)=="real") {
2460   " Singular cannot factorize over 'real' as ground field";
2461   return(list());
2462 }
2463 if (size(maxideal(1))<2) {
2464   " A univariate polynomial ring makes no sense !";
2465   return(list());
2466 }
2467 if ((size(maxideal(1))>2) && (printlevel > -1)) {
2468   " Warning: all but the first two variables are ignored!";
2469 }
2470 if (find(charstr(basering),string(char(basering)))!=1) {
2471   " ring of type (p^k,a) not implemented";
2472 //----------------------------------------------------------------------------
2473 // weder primitives Element noch factorize noch map "char p^k" -> "char -p"
2474 // [(p^k,a)->(p,a) ground field] noch fetch
2475 //----------------------------------------------------------------------------
2476   return(list());
2477 }
2478 //----------------- Definition eines neuen Ringes: HNEring -------------------
2479 string namex=varstr(1); string namey=varstr(2);
2480 if (string(char(altring))==charstr(altring)) {       // kein Parameter
2481   ring HNEring = char(altring),(x,y),ls;
2482   map m=altring,x,y;
2483   poly f=m(f);
2484   kill m;
2485 }
2486 else {
2487   string mipl=string(minpoly);
2488   if (mipl=="0") {
2489     " ** WARNING: No algebraic extension of this ground field is possible!";
2490     " ** We try to develop this polynomial, but if the need for an extension";
2491     " ** occurs during the calculation, we cannot proceed with the";
2492     " ** corresponding branches ...";
2493     execute("ring HNEring=("+charstr(basering)+"),(x,y),ls;");
2494 //--- ring ...=(char(.),`parstr()`),... geht nicht, wenn mehr als 1 Param. ---
2495   }
2496   else {
2497    string pa=parstr(altring);
2498    ring HNhelpring=p,`pa`,dp;
2499    execute("poly mipo="+mipl+";");  // Minimalpolynom in Polynom umgewandelt
2500    ring HNEring=(p,a),(x,y),ls;
2501    map getminpol=HNhelpring,a;
2502    mipl=string(getminpol(mipo));    // String umgewandelt mit 'a' als Param.
2503    execute("minpoly="+mipl+";");     // "minpoly=poly is not supported"
2504    kill HNhelpring, getminpol;
2505   }
2506   if (nvars(altring)==2) { poly f=fetch(altring,f); }
2507   else {
2508     map m=altring,x,y;
2509     poly f=m(f);
2510     kill m;
2511   }
2512 }
2513 export HNEring;
2514
2515 if (defined(HNDebugOn))
2516 {"received polynomial: ",f,", with x =",namex,", y =",namey;}
2517
2518 //----------------------- Variablendefinitionen ------------------------------
2519 int Abbruch,i,NullHNEx,NullHNEy;
2520 string str;
2521 list Newton,Ergebnis,hilflist;
2522
2523 //====================== Tests auf Zulaessigkeit des Polynoms ================
2524
2525 //-------------------------- Test, ob Einheit oder Null ----------------------
2526 if (subst(subst(f,x,0),y,0)!=0) {
2527   dbprint(printlevel+1,
2528           "The given polynomial is a unit in the power series ring!");
2529   keepring HNEring;
2530   return(list());                   // there are no HNEs
2531 }
2532 if (f==0) {
2533   dbprint(printlevel+1,"The given polynomial is zero!");
2534   keepring HNEring;
2535   return(list());                   // there are no HNEs
2536 }
2537
2538 //-----------------------  Test auf Quadratfreiheit --------------------------
2539
2540 if ((p==0) and (size(charstr(basering))==1)) {
2541
2542 //-------- Fall basering==0,... : Wechsel in Ring mit char >0 ----------------
2543 // weil squarefree eine Standardbasis berechnen muss (verwendet Syzygien)
2544 // -- wenn f in diesem Ring quadratfrei ist, dann erst recht im Ring HNEring
2545 //----------------------------------------------------------------------------
2546  int testerg=(polytest(f)==0);
2547  ring zweitring = 32003,(x,y),dp;
2548
2549  map polyhinueber=HNEring,x,y;         // fetch geht nicht
2550  poly f=polyhinueber(f);
2551  poly test_sqr=squarefree(f);
2552  if (test_sqr != f) {
2553   if (printlevel>0) {
2554     "Most probably the given polynomial is not squarefree. But the test was";
2555     "made in characteristic 32003 and not 0 to improve speed. You can";
2556     "(r) redo the test in char 0 (but this may take some time)";
2557     "(c) continue the development, if you're sure that the polynomial IS",
2558     "squarefree";
2559     if (testerg==1) {
2560       "(s) continue the development with a squarefree factor (*)";}
2561     "(q) or just quit the algorithm (default action)";
2562     "";"Please enter the letter of your choice:";
2563     str=read("")[1];             // reads one character
2564   }
2565   else { str="r"; }              // printlevel <= 0: non-interactive behaviour
2566   setring HNEring;
2567   map polyhinueber=zweitring,x,y;
2568   if (str=="r") {
2569     poly test_sqr=squarefree(f);
2570     if (test_sqr != f) {
2571      if (printlevel>0) { "The given polynomial is in fact not squarefree."; }
2572      else              { "The given polynomial is not squarefree!"; }
2573      "I'll continue with the radical.";
2574      f=test_sqr;
2575     }
2576     else {
2577      dbprint(printlevel,
2578       "everything is ok -- the polynomial is squarefree in characteristic 0");
2579     }
2580   }
2581   else {
2582     if ((str=="s") and (testerg==1)) {
2583       "(*)attention: it could be that the factor is only one in char 32003!";
2584       f=polyhinueber(test_sqr);
2585     }
2586     else {
2587       if (str<>"c") {
2588         setring altring;
2589         if(system("with","Namespaces")) { kill Top::HNEring; }
2590         kill HNEring;kill zweitring;
2591         return(list());}
2592       else { "if the algorithm doesn't terminate, you were wrong...";}
2593   }}
2594   kill zweitring;
2595   if (defined(HNDebugOn)) {"I continue with the polynomial",f; }
2596  }
2597  else {
2598    setring HNEring;
2599    kill zweitring;
2600  }
2601 }
2602 //------------------ Fall Char > 0 oder Ring hat Parameter -------------------
2603 else {
2604  poly test_sqr=squarefree(f);
2605  if (test_sqr != f) {
2606   if (printlevel>0) {
2607    if (test_sqr == 1) {
2608     "The given polynomial is of the form g^"+string(p)+",";
2609     "therefore not squarefree.  You can:";
2610     " (q) quit the algorithm (recommended) or";
2611     " (f) continue with the full radical (using a factorization of the";
2612     "     pure power part; this could take much time)";
2613     "";"Please enter the letter of your choice:";
2614     str=read("")[1];
2615     if (str<>"f") { str="q"; }
2616    }
2617    else {
2618     "The given polynomial is not squarefree.";
2619     if (p != 0)
2620      {
2621       " You can:";
2622       " (c) continue with a squarefree divisor (but factors of the form g^"
2623       +string(p);
2624       "     are lost; this is recommended, takes no more time)";
2625       " (f) continue with the full radical (using a factorization of the";
2626       "     pure power part; this could take much time)";
2627       " (q) quit the algorithm";
2628       "";"Please enter the letter of your choice:";
2629       str=read("")[1];
2630       if ((str<>"f") && (str<>"q")) { str="c"; }
2631      }
2632     else { "I'll continue with the radical."; str="c"; }
2633    }                                // endelse (test_sqr!=1)
2634   }
2635   else {
2636     "//** Error: The given polynomial is not squarefree!";
2637     "//** Since the global variable `printlevel' has the value",printlevel,
2638       "we stop here.";
2639     "//   Either call me again with a squarefree polynomial f or assign";
2640     "            printlevel=1;";
2641     "//   before calling me with a non-squarefree f.";
2642     "//   If printlevel > 0, I will present to you some possibilities how to",
2643       "proceed.";
2644     str="q";
2645   }
2646   if (str=="q") {
2647    if(system("with","Namespaces")) { kill Top::HNEring; }
2648    setring altring;kill HNEring;
2649    return(list());
2650   }
2651   if (str=="c") { f=test_sqr; }
2652   if (str=="f") { f=allsquarefree(f,test_sqr); }
2653  }
2654  if (defined(HNDebugOn)) {"I continue with the polynomial",f; }
2655
2656 }
2657 //====================== Ende Test auf Quadratfreiheit =======================
2658 if (subst(subst(f,x,0),y,0)!=0) {
2659   "Sorry. The remaining polynomial is a unit in the power series ring...";
2660   keepring HNEring;
2661   return(list());
2662 }
2663 //---------------------- Test, ob f teilbar durch x oder y -------------------
2664 if (subst(f,y,0)==0) {
2665   f=f/y; NullHNEy=1; }             // y=0 is a solution
2666 if (subst(f,x,0)==0) {
2667   f=f/x; NullHNEx=1; }             // x=0 is a solution
2668
2669 Newton=newtonpoly(f);
2670 i=1; Abbruch=0;
2671 //----------------------------------------------------------------------------
2672 // finde Eckpkt. des Newtonpolys, der den Teil abgrenzt, fuer den x transvers:
2673 // Annahme: Newton ist sortiert, s.d. Newton[1]=Punkt auf der y-Achse,
2674 // Newton[letzt]=Punkt auf der x-Achse
2675 //----------------------------------------------------------------------------
2676 while ((i<size(Newton)) and (Abbruch==0)) {
2677  if ((Newton[i+1][1]-Newton[i][1])>=(Newton[i][2]-Newton[i+1][2]))
2678   {Abbruch=1;}
2679  else {i=i+1;}
2680 }
2681 int grenze1=Newton[i][2];
2682 int grenze2=Newton[i][1];
2683 //----------------------------------------------------------------------------
2684 // Stelle Ring bereit zur Uebertragung der Daten im Fall einer Koerperer-
2685 // weiterung. Definiere Objekte, die spaeter uebertragen werden.
2686 // Binde die Listen (azeilen,...) an den Ring (um sie nicht zu ueberschreiben
2687 // bei Def. in einem anderen Ring).
2688 // Exportiere Objekte, damit sie auch in der proc HN noch da sind
2689 //----------------------------------------------------------------------------
2690 ring HNE_noparam = char(altring),(a,x,y),ls;
2691 export HNE_noparam;
2692 poly f;
2693 list azeilen=ideal(0);
2694 list HNEs=ideal(0);
2695 list aneu=ideal(0);
2696 list faktoren=ideal(0);
2697 ideal deltais;
2698 poly delta;                   // nicht number, weil delta von a abhaengen kann
2699 export f,azeilen,HNEs,aneu,faktoren,deltais,delta;
2700 //----- hier steht die Anzahl bisher benoetigter Ringerweiterungen drin: -----
2701 int EXTHNEnumber=0; export EXTHNEnumber;
2702 setring HNEring;
2703
2704 // ================= Die eigentliche Berechnung der HNE: =====================
2705
2706 // ------- Berechne HNE von allen Zweigen, fuer die x transversal ist: -------
2707 if (defined(HNDebugOn))
2708   {"1st step: Treat Newton polygon until height",grenze1;}
2709 if (grenze1>0) {
2710  hilflist=HN(f,grenze1,1,essential);
2711  if (typeof(hilflist[1][1])=="ideal") { hilflist[1]=list(); }
2712 //- fuer den Fall, dass keine Zweige in transz. Erw. berechnet werden konnten-
2713  Ergebnis=extractHNEs(hilflist[1],0);
2714  if (hilflist[2]!=-1) {
2715    if (defined(HNDebugOn)) {" ring change in HN(",1,") detected";}
2716    poly transfproc=hilflist[2];
2717    map hole=HNE_noparam,transfproc,x,y;
2718    setring HNE_noparam;
2719    f=imap(HNEring,f);
2720    setring EXTHNEring(EXTHNEnumber);
2721    poly f=hole(f);
2722  }
2723 }
2724 if (NullHNEy==1) {
2725  Ergebnis=Ergebnis+list(list(matrix(ideal(0,x)),intvec(1),int(0),poly(0)));
2726 }
2727 // --------------- Berechne HNE von allen verbliebenen Zweigen: --------------
2728 if (defined(HNDebugOn))
2729    {"2nd step: Treat Newton polygon until height",grenze2;}
2730 if (grenze2>0) {
2731  map xytausch=basering,y,x;
2732  kill hilflist;
2733  def letztring=basering;
2734  if (EXTHNEnumber==0) { setring HNEring; }
2735  else                 { setring EXTHNEring(EXTHNEnumber); }
2736  list hilflist=HN(xytausch(f),grenze2,1,essential);
2737  if (typeof(hilflist[1][1])=="ideal") { hilflist[1]=list(); }
2738  if (not defined(Ergebnis)) {
2739 //-- HN wurde schon mal ausgefuehrt; Ringwechsel beim zweiten Aufruf von HN --
2740    if (defined(HNDebugOn)) {" ring change in HN(",1,") detected";}
2741    poly transfproc=hilflist[2];
2742    map hole=HNE_noparam,transfproc,x,y;
2743    setring HNE_noparam;
2744    list Ergebnis=imap(letztring,Ergebnis);
2745    setring EXTHNEring(EXTHNEnumber);
2746    list Ergebnis=hole(Ergebnis);
2747  }
2748  Ergebnis=Ergebnis+extractHNEs(hilflist[1],1);
2749 }
2750 if (NullHNEx==1) {
2751  Ergebnis=Ergebnis+list(list(matrix(ideal(0,x)),intvec(1),int(1),poly(0)));
2752 }
2753 //------------------- Loesche globale, nicht mehr benoetigte Objekte: --------
2754 if (EXTHNEnumber>0) {
2755  if(system("with","Namespaces")) { kill Top::HNEring; }
2756  kill HNEring;
2757  def HNEring=EXTHNEring(EXTHNEnumber);
2758  setring HNEring;
2759  export HNEring;
2760  kill EXTHNEring(1..EXTHNEnumber);
2761 }
2762 kill HNE_noparam;
2763 kill EXTHNEnumber;
2764 keepring basering;
2765 return(Ergebnis);
2766}
2767
2768///////////////////////////////////////////////////////////////////////////////
2769proc essdevelop (poly f)
2770"USAGE:   essdevelop(f); f poly
2771RETURN:  Hamburger-Noether development of essential branches of f:
2772         A list of lists in the form of develop(f)
2773         (matrix,intvec,int,poly -- the last int indicating irreducibility is
2774         omitted); each entry contains the data for one of the branches of f.
2775         For more details type `help develop;'
2776CREATE:  a ring with name `HNEring', variables `x,y' and ordering `ls' over
2777         a field extension of the current basering's ground field.
2778         As the Hamburger-Noether development of a reducible curve normally
2779         does not exist in the given basering, @code{essdevelop} always defines
2780         HNEring and changes to it. The field extension is chosen minimal.
2781NOTE:    If the HNE needs a field extension, some of the branches will be
2782         conjugate. In this case @code{essdevelop} reduces the computation to
2783         one representative for each group of conjugate branches.
2784         Note that the degree of each branch is in general less than the degree
2785         of the field extension in which all HNEs can be put.
2786
2787         Use @code{reddevelop} or @code{HNdevelop} to compute a complete HNE,
2788         i.e. a HNE for all branches.
2789SEE ALSO: develop, reddevelop, HNdevelop, extdevelop
2790EXAMPLE: example essdevelop;  shows an example
2791"
2792{
2793 list Ergebnis=pre_HN(f,1);
2794 dbprint(printlevel+1,
2795    "// result: "+string(size(Ergebnis))+" branch(es) successfully computed;");
2796 if (string(minpoly) <> "0") {
2797   dbprint(printlevel+1,
2798    "// note that conjugate branches are omitted and that the number",
2799    "// of branches represented by each remaining one may vary!");
2800 }
2801 dbprint(printlevel+1,
2802    "// basering has changed to HNEring");
2803 keepring basering;
2804 return(Ergebnis);
2805}
2806example
2807{
2808  // -------- prepare for example ---------
2809  if (nameof(basering)=="HNEring") {
2810   def rettering=HNEring;
2811   kill HNEring;
2812  }
2813  // ------ the example starts here -------
2814  "EXAMPLE:"; echo = 2;
2815  ring r=2,(x,y),dp;
2816  poly f=(x4+x2y+y2)*(x3+xy2+y3);
2817  // --------- compute all branches: ---------
2818  list hne=reddevelop(f);
2819  displayHNE(hne);
2820  setring r;
2821  // --- compute only one of conjugate branches: ---
2822  list hne=essdevelop(f);
2823  displayHNE(hne);
2824  // nr. 1 of essdevelop represents nr. 1 - 3 of reddevelop and
2825  // nr. 2 of essdevelop represents nr. 4 + 5 of reddevelop
2826  echo = 0;
2827  // --- restore HNEring if previously defined ---
2828  if (defined(rettering)) {
2829   setring rettering;
2830   def HNEring=rettering;
2831   export HNEring;
2832  }
2833}
2834
2835///////////////////////////////////////////////////////////////////////////////
2836static proc HN (poly f,int grenze, int Aufruf_Ebene, int essential)
2837"NOTE: This procedure is only for internal use, it is called via pre_HN"
2838{
2839 //---------- Variablendefinitionen fuer den unverzweigten Teil: --------------
2840 if (defined(HNDebugOn)) {"procedure HN",Aufruf_Ebene;}
2841 int Abbruch,ende,i,j,e,M,N,Q,R,zeiger,zeile,zeilevorher;
2842 intvec hqs;
2843 poly fvorher;
2844 list erg=ideal(0); list HNEs=ideal(0); // um die Listen an den Ring zu binden
2845
2846 //-------------------- Bedeutung von Abbruch: --------------------------------
2847 //------- 0:keine Verzweigung | 1:Verzweigung,nicht fertig | 2:fertig --------
2848 //
2849 // Struktur von HNEs : Liste von Listen L (fuer jeden Zweig) der Form
2850 // L[1]=intvec (hqs), L[2],L[3],... ideal (die Zeilen (0,1,...) der HNE)
2851 // L[letztes]=poly (transformiertes f)
2852 //----------------------------------------------------------------------------
2853 list Newton;
2854 number delta;
2855 int p = char(basering);                // Ringcharakteristik
2856 list azeilen=ideal(0);
2857 ideal hilfid; list hilflist=ideal(0); intvec hilfvec;
2858
2859 // ======================= der unverzweigte Teil: ============================
2860 while (Abbruch==0) {
2861  Newton=newtonpoly(f);
2862  zeiger=find_in_list(Newton,grenze);
2863  if (Newton[zeiger][2] != grenze)
2864    {"Didn't find an edge in the Newton polygon!";}
2865  if (zeiger==size(Newton)-1) {
2866    if (defined(HNDebugOn)) {"only one relevant side in Newton polygon";}
2867    M=Newton[zeiger+1][1]-Newton[zeiger][1];
2868    N=Newton[zeiger][2]-Newton[zeiger+1][2];
2869    R = M%N;
2870    Q = M / N;
2871
2872 //-------- 1. Versuch: ist der quasihomogene Leitterm reine Potenz ? ---------
2873 //              (dann geht alles wie im irreduziblen Fall)
2874 //----------------------------------------------------------------------------
2875    e = gcd(M,N);
2876    delta=factorfirst(redleit(f,Newton[zeiger],Newton[zeiger+1])
2877                      /x^Newton[zeiger][1],M,N);
2878    if (delta==0) {
2879      if (defined(HNDebugOn)) {" The given polynomial is reducible !";}
2880      Abbruch=1;
2881    }
2882    if (Abbruch==0) {
2883 //-------------- f,zeile retten fuer den Spezialfall (###): ------------------
2884      fvorher=f;zeilevorher=zeile;
2885      if (R==0) {
2886 //------------- transformiere f mit T1, wenn kein Abbruch nachher: -----------
2887        if (N>1) { f = T1_Transform(f,delta,M/ e); }
2888        else     { ende=1; }
2889        if (defined(HNDebugOn)) {"a("+string(zeile)+","+string(Q)+") =",delta;}
2890        azeilen[zeile+1][Q]=delta;
2891      }
2892      else {
2893 //------------- R > 0 : transformiere f mit T2 -------------------------------
2894        erg=T2_Transform(f,delta,M,N,referencepoly(Newton));
2895        f=erg[1];delta=erg[2];
2896 //------- vollziehe Euklid.Alg. nach, um die HN-Matrix zu berechnen: ---------
2897        while (R!=0) {
2898         if (defined(HNDebugOn)) { "h("+string(zeile)+") =",Q; }
2899         hqs[zeile+1]=Q;         // denn zeile beginnt mit dem Wert 0
2900 //------------------ markiere das Zeilenende der HNE: ------------------------
2901         azeilen[zeile+1][Q+1]=x;
2902         zeile=zeile+1;
2903 //----------- Bereitstellung von Speicherplatz fuer eine neue Zeile: ---------
2904         azeilen[zeile+1]=ideal(0);
2905         M=N; N=R; R=M%N; Q=M / N;
2906        }
2907        if (defined(HNDebugOn)) {"a("+string(zeile)+","+string(Q)+") =",delta;}
2908        azeilen[zeile+1][Q]=delta;
2909      }
2910      if (defined(HNDebugOn)) {"transformed polynomial: ",f;}
2911      grenze=e;
2912 //----------------------- teste Abbruchbedingungen: --------------------------
2913      if (subst(f,y,0)==0) {              // <==> y|f
2914        dbprint(printlevel+1,"finite HNE of one branch found");
2915           // voice abzufragen macht bei rekursiven procs keinen Sinn
2916        azeilen[zeile+1][Q+1]=x;
2917 //- Q wird nur in hqs eingetragen, wenn der Spezialfall nicht eintritt (s.u.)-
2918        Abbruch=2;
2919        if (grenze>1) {
2920         if (jet(f,1,intvec(0,1))==0) {
2921 //------ jet(...)=alle Monome von f, die nicht durch y2 teilbar sind ---------
2922 "THE TEST FOR SQUAREFREENESS WAS BAD!! The polynomial was NOT squarefree!!!";}
2923         else {
2924 //-------------------------- Spezialfall (###): ------------------------------
2925 // Wir haben das Problem, dass die HNE eines Zweiges hier abbricht, aber ein
2926 // anderer Zweig bis hierher genau die gleiche HNE hat, die noch weiter geht
2927 // Loesung: mache Transform. rueckgaengig und behandle f im Verzweigungsteil
2928 //----------------------------------------------------------------------------
2929          Abbruch=1;
2930          f=fvorher;zeile=zeilevorher;grenze=Newton[zeiger][2];
2931        }}
2932        else {f=0;}     // f nicht mehr gebraucht - spare Speicher
2933        if (Abbruch==2) { hqs[zeile+1]=Q; }
2934      }                 // Spezialfall nicht eingetreten
2935      else {
2936        if (ende==1) {
2937          dbprint(printlevel+1,"HNE of one branch found");
2938          Abbruch=2; hqs[zeile+1]=-Q-1;}
2939      }
2940    }                   // end(if Abbruch==0)
2941  }                     // end(if zeiger...)
2942  else { Abbruch=1;}
2943 }                      // end(while Abbruch==0)
2944
2945 // ===================== der Teil bei Verzweigung: ===========================
2946
2947 if (Abbruch==1) {
2948 //---------- Variablendefinitionen fuer den verzweigten Teil: ----------------
2949  poly leitf,teiler,transformiert;
2950  list aneu=ideal(0);
2951  list faktoren;
2952  list HNEakut=ideal(0);
2953  ideal deltais;
2954  intvec eis;
2955  int zaehler,hnezaehler,zl,zl1,M1,N1,R1,Q1,needext;
2956  int numberofRingchanges,lastRingnumber,ringischanged,flag;
2957  string letztringname;
2958
2959  zeiger=find_in_list(Newton,grenze);
2960  if (defined(HNDebugOn)) {
2961    "Branching part reached---Newton polygon :",Newton;
2962    "relevant part until height",grenze,", from",Newton[zeiger],"on";
2963  }
2964  azeilen=list(hqs)+azeilen; // hat jetzt Struktur von HNEs: hqs in der 1.Zeile
2965
2966 //======= Schleife fuer jede zu betrachtende Seite des Newtonpolygons: =======
2967  for(i=zeiger; i<size(Newton); i++) {
2968   if (defined(HNDebugOn)) { "we consider side",Newton[i],Newton[i+1]; }
2969   M=Newton[i+1][1]-Newton[i][1];
2970   N=Newton[i][2]-Newton[i+1][2];
2971   R = M%N;
2972   Q = M / N;
2973   e=gcd(M,N);
2974   needext=1;
2975   letztringname=nameof(basering);
2976   lastRingnumber=EXTHNEnumber;
2977   faktoren=list(ideal(charPoly(redleit(f,Newton[i],Newton[i+1])
2978                       /(x^Newton[i][1]*y^Newton[i+1][2]),M,N)  ),
2979                 intvec(1));                  // = (zu faktoriserendes Poly, 1)
2980
2981 //-- wechsle so lange in Ringerw., bis Leitform vollst. in Linearfakt. zerf.:-
2982   for (numberofRingchanges=1; needext==1; numberofRingchanges++) {
2983    leitf=redleit(f,Newton[i],Newton[i+1])/(x^Newton[i][1]*y^Newton[i+1][2]);
2984    delta=factorfirst(leitf,M,N);
2985    needext=0;
2986    if (delta==0) {
2987
2988 //---------- Sonderbehandlung: faktorisere einige Polynome ueber Q(a): -------
2989     if (charstr(basering)=="0,a") {
2990       faktoren,flag=extrafactor(leitf,M,N);  // damit funktion. Bsp. Baladi 5
2991       if (flag==0)
2992         { ERROR("Could not factorize in field of type (0,a)!"); }
2993     }
2994     else {
2995 //------------------ faktorisiere das charakt. Polynom: ----------------------
2996       if ((numberofRingchanges==1) or (essential==0)) {
2997         faktoren=factorlist(faktoren);
2998       }
2999       else {     // eliminiere alle konjugierten Nullstellen bis auf eine:
3000         ideal hilf_id;
3001         for (zaehler=1; zaehler<=size(faktoren[1]); zaehler++) {
3002           hilf_id=factorize(faktoren[1][zaehler],0)[1];
3003           if (size(hilf_id)>1) { faktoren[1][zaehler]=hilf_id[2]; }
3004           else                 { faktoren[1][zaehler]=hilf_id[1]; }
3005         }
3006       }
3007     }
3008
3009     zaehler=1; eis=0;
3010     for (j=1; j<=size(faktoren[2]); j++) {
3011      teiler=faktoren[1][j];
3012      if (teiler/y != 0) {         // sonst war's eine Einheit --> wegwerfen!
3013        if (defined(HNDebugOn)) {"factor of leading form found:",teiler;}
3014        if (teiler/y2 == 0) {      // --> Faktor hat die Form cy+d
3015          deltais[zaehler]=-subst(teiler,y,0)/koeff(teiler,0,1); //=-d/c
3016          eis[zaehler]=faktoren[2][j];
3017          zaehler++;
3018        }
3019        else {
3020          dbprint(printlevel+1,
3021             " Change of basering (field extension) necessary!");
3022          if (defined(HNDebugOn)) { teiler,"is not properly factored!"; }
3023          if (needext==0) { poly zerlege=teiler; }
3024          needext=1;
3025        }
3026      }
3027     }                             // end(for j)
3028    }
3029    else { deltais=ideal(delta); eis=e;}
3030    if (defined(HNDebugOn)) {"roots of char. poly:";deltais;
3031                             "with multiplicities:",eis;}
3032    if (needext==1) {
3033 //--------------------- fuehre den Ringwechsel aus: --------------------------
3034      ringischanged=1;
3035      if ((size(parstr(basering))>0) && string(minpoly)=="0") {
3036        " ** We've had bad luck! The HNE cannot completely be calculated!";
3037                                   // HNE in transzendenter Erw. fehlgeschlagen
3038        kill zerlege;
3039        ringischanged=0; break;    // weiter mit gefundenen Faktoren
3040      }
3041      if (parstr(basering)=="") {
3042        EXTHNEnumber++;
3043        splitring(zerlege,"EXTHNEring("+string(EXTHNEnumber)+")");
3044        poly transf=0;
3045        poly transfproc=0;
3046      }
3047      else {
3048        if (defined(translist)) { kill translist; } // Vermeidung einer Warnung
3049        if (numberofRingchanges>1) {  // ein Ringwechsel hat nicht gereicht
3050         list translist=splitring(zerlege,"",list(transf,transfproc,faktoren));
3051         poly transf=translist[1];
3052         poly transfproc=translist[2];
3053         list faktoren=translist[3];
3054        }
3055        else {
3056         if (defined(transfproc)) { // in dieser proc geschah schon Ringwechsel
3057          EXTHNEnumber++;
3058          list translist=splitring(zerlege,"EXTHNEring("
3059               +string(EXTHNEnumber)+")",list(a,transfproc));
3060          poly transf=translist[1];
3061          poly transfproc=translist[2];
3062         }
3063         else {
3064          EXTHNEnumber++;
3065          list translist=splitring(zerlege,"EXTHNEring("
3066               +string(EXTHNEnumber)+")",a);
3067          poly transf=translist[1];
3068          poly transfproc=transf;
3069        }}
3070      }
3071 //----------------------------------------------------------------------------
3072 // transf enthaelt jetzt den alten Parameter des Ringes, der aktiv war vor
3073 // Beginn der Schleife (evtl. also ueber mehrere Ringwechsel weitergereicht),
3074 // transfproc enthaelt den alten Parm. des R., der aktiv war zu Beginn der
3075 // Prozedur, und der an die aufrufende Prozedur zurueckgegeben werden muss
3076 // transf ist Null, falls der alte Ring keinen Parameter hatte,
3077 // das gleiche gilt fuer transfproc
3078 //----------------------------------------------------------------------------
3079
3080 //------ Neudef. von Variablen, Uebertragung bisher errechneter Daten: -------
3081      poly leitf,teiler,transformiert;
3082      list aneu=ideal(0);
3083      ideal deltais;
3084      number delta;
3085      setring HNE_noparam;
3086      if (defined(letztring)) { kill letztring; }
3087      if (lastRingnumber>0) { def letztring=EXTHNEring(lastRingnumber); }
3088      else                  { def letztring=HNEring; }
3089      f=imap(letztring,f);
3090      faktoren=imap(letztring,faktoren);
3091      setring EXTHNEring(EXTHNEnumber);
3092      map hole=HNE_noparam,transf,x,y;
3093      poly f=hole(f);
3094      if (not defined(faktoren)) {
3095        list faktoren=hole(faktoren);
3096      }
3097    }
3098   }    // end (while needext==1) bzw. for (numberofRingchanges)
3099
3100   if (eis==0) { i++; continue; }
3101   if (ringischanged==1) {
3102    list erg,hilflist,HNEakut;            // dienen nur zum Sp. von Zwi.erg.
3103    ideal hilfid;
3104    erg=ideal(0); hilflist=erg; HNEakut=erg;
3105
3106    hole=HNE_noparam,transf,x,y;
3107    setring HNE_noparam;
3108    azeilen=imap(letztring,azeilen);
3109    HNEs=imap(letztring,HNEs);
3110
3111    setring EXTHNEring(EXTHNEnumber);
3112    list azeilen=hole(azeilen);
3113    list HNEs=hole(HNEs);
3114    kill letztring;
3115    ringischanged=0;
3116   }
3117
3118 //============ Schleife fuer jeden gefundenen Faktor der Leitform: ===========
3119   for (j=1; j<=size(eis); j++) {
3120 //-- Mache Transf. T1 oder T2, trage Daten in HNEs ein, falls HNE abbricht: --
3121
3122 //------------------------ Fall R==0: ----------------------------------------
3123    if (R==0) {
3124      transformiert = T1_Transform(f,number(deltais[j]),M/ e);
3125      if (defined(HNDebugOn)) {
3126        "a("+string(zeile)+","+string(Q)+") =",deltais[j];
3127        "transformed polynomial: ",transformiert;
3128      }
3129      if (subst(transformiert,y,0)==0) {
3130       dbprint(printlevel+1,"finite HNE found");
3131       hnezaehler++;
3132 //------------ trage deltais[j],x ein in letzte Zeile, fertig: ---------------
3133       HNEakut=azeilen+list(poly(0));        // =HNEs[hnezaehler];
3134       hilfid=HNEakut[zeile+2]; hilfid[Q]=deltais[j]; hilfid[Q+1]=x;
3135       HNEakut[zeile+2]=hilfid;
3136       HNEakut[1][zeile+1]=Q;                // aktualisiere Vektor mit den hqs
3137       HNEs[hnezaehler]=HNEakut;
3138       if (eis[j]>1) {
3139        transformiert=transformiert/y;
3140        if (subst(transformiert,y,0)==0) {
3141 "THE TEST FOR SQUAREFREENESS WAS BAD!! The polynomial was NOT squarefree!!!";}
3142        else {
3143 //------ Spezialfall (###) eingetreten: Noch weitere Zweige vorhanden --------
3144          eis[j]=eis[j]-1;
3145        }
3146       }
3147      }
3148    }
3149    else {
3150 //------------------------ Fall R <> 0: --------------------------------------
3151      erg=T2_Transform(f,number(deltais[j]),M,N,referencepoly(Newton));
3152      transformiert=erg[1];delta=erg[2];
3153      if (defined(HNDebugOn)) {"transformed polynomial: ",transformiert;}
3154      if (subst(transformiert,y,0)==0) {
3155       dbprint(printlevel+1,"finite HNE found");
3156       hnezaehler++;
3157 //---------------- trage endliche HNE in HNEs ein: ---------------------------
3158       HNEakut=azeilen;           // dupliziere den gemeins. Anfang der HNE's
3159       zl=2;                      // (kommt schliesslich nach HNEs[hnezaehler])
3160 //----------------------------------------------------------------------------
3161 // Werte von:  zeile: aktuelle Zeilennummer der HNE (gemeinsamer Teil)
3162 //             zl   : die HNE spaltet auf; zeile+zl ist der Index fuer die
3163 // Zeile des aktuellen Zweigs; (zeile+zl-2) ist die tatsaechl. Zeilennr.
3164 // (bei 0 angefangen) der HNE  ([1] <- intvec(hqs), [2] <- 0. Zeile usw.)
3165 //----------------------------------------------------------------------------
3166
3167 //---------- vollziehe Euklid.Alg. nach, um die HN-Matrix zu berechnen: ------
3168       M1=M;N1=N;R1=R;Q1=M1/ N1;
3169       while (R1!=0) {
3170        if (defined(HNDebugOn)) { "h("+string(zeile+zl-2)+") =",Q1; }
3171        HNEakut[1][zeile+zl-1]=Q1;
3172        HNEakut[zeile+zl][Q1+1]=x;
3173                                  // markiere das Zeilenende der HNE
3174        zl=zl+1;
3175 //-------- Bereitstellung von Speicherplatz fuer eine neue Zeile: ------------
3176        HNEakut[zeile+zl]=ideal(0);
3177
3178        M1=N1; N1=R1; R1=M1%N1; Q1=M1 / N1;
3179       }
3180       if (defined(HNDebugOn)) {
3181         "a("+string(zeile+zl-2)+","+string(Q1)+") =",delta;
3182       }
3183       HNEakut[zeile+zl][Q1]  =delta;
3184       HNEakut[zeile+zl][Q1+1]=x;
3185       HNEakut[1][zeile+zl-1] =Q1;     // aktualisiere Vektor mit hqs
3186       HNEakut[zeile+zl+1]=poly(0);
3187       HNEs[hnezaehler]=HNEakut;
3188 //-------------------- Ende der Eintragungen in HNEs -------------------------
3189
3190       if (eis[j]>1) {
3191        transformiert=transformiert/y;
3192        if (subst(transformiert,y,0)==0) {
3193 "THE TEST FOR SQUAREFREENESS WAS BAD!! The polynomial was NOT squarefree!!!";}
3194         else {
3195 //--------- Spezialfall (###) eingetreten: Noch weitere Zweige vorhanden -----
3196          eis[j]=eis[j]-1;
3197       }}
3198      }                           // endif (subst()==0)
3199    }                             // endelse (R<>0)
3200
3201 //========== Falls HNE nicht abbricht: Rekursiver Aufruf von HN: =============
3202 //------------------- Berechne HNE von transformiert -------------------------
3203    if (subst(transformiert,y,0)!=0) {
3204     lastRingnumber=EXTHNEnumber;
3205     list HNerg=HN(transformiert,eis[j],Aufruf_Ebene+1,essential);
3206     if (HNerg[2]==-1) {          // kein Ringwechsel in HN aufgetreten
3207       aneu=HNerg[1];  }
3208     else {
3209       if (defined(HNDebugOn))
3210          {" ring change in HN(",Aufruf_Ebene+1,") detected";}
3211       list aneu=HNerg[1];
3212       poly transfproc=HNerg[2];
3213
3214 //- stelle lokale Var. im neuen Ring wieder her und rette ggf. ihren Inhalt: -
3215       list erg,hilflist,faktoren,HNEakut;
3216       ideal hilfid;
3217       erg=ideal(0); hilflist=erg; faktoren=erg; HNEakut=erg;
3218       poly leitf,teiler,transformiert;
3219
3220       map hole=HNE_noparam,transfproc,x,y;
3221       setring HNE_noparam;
3222       if (lastRingnumber>0) { def letztring=EXTHNEring(lastRingnumber); }
3223       else                  { def letztring=HNEring; }
3224       HNEs=imap(letztring,HNEs);
3225       azeilen=imap(letztring,azeilen);
3226       deltais=imap(letztring,deltais);
3227       delta=imap(letztring,delta);
3228       f=imap(letztring,f);
3229
3230       setring EXTHNEring(EXTHNEnumber);
3231       list HNEs=hole(HNEs);
3232       list azeilen=hole(azeilen);
3233       ideal deltais=hole(deltais);
3234       number delta=number(hole(delta));
3235       poly f=hole(f);
3236     }
3237     kill HNerg;
3238 //----------------------------------------------------------------------------
3239 // HNerg muss jedesmal mit "list" neu definiert werden, weil vorher noch nicht
3240 // ------- klar ist, ob der Ring nach Aufruf von HN noch derselbe ist --------
3241
3242 //============= Verknuepfe bisherige HNE mit von HN gelieferten HNEs: ========
3243     if (R==0) {
3244       HNEs,hnezaehler=constructHNEs(HNEs,hnezaehler,aneu,azeilen,zeile,
3245                       deltais,Q,j);
3246     }
3247     else {
3248      for (zaehler=1; zaehler<=size(aneu); zaehler++) {
3249       hnezaehler++;
3250       HNEakut=azeilen;          // dupliziere den gemeinsamen Anfang der HNE's
3251       zl=2;                     // (kommt schliesslich nach HNEs[hnezaehler])
3252 //---------------- Trage Beitrag dieser Transformation T2 ein: ---------------
3253 //--------- Zur Bedeutung von zeile, zl: siehe Kommentar weiter oben ---------
3254
3255 //--------- vollziehe Euklid.Alg. nach, um die HN-Matrix zu berechnen: -------
3256       M1=M;N1=N;R1=R;Q1=M1/ N1;
3257       while (R1!=0) {
3258        if (defined(HNDebugOn)) { "h("+string(zeile+zl-2)+") =",Q1; }
3259        HNEakut[1][zeile+zl-1]=Q1;
3260        HNEakut[zeile+zl][Q1+1]=x;    // Markierung des Zeilenendes der HNE
3261        zl=zl+1;
3262 //-------- Bereitstellung von Speicherplatz fuer eine neue Zeile: ------------
3263        HNEakut[zeile+zl]=ideal(0);
3264        M1=N1; N1=R1; R1=M1%N1; Q1=M1 / N1;
3265       }
3266       if (defined(HNDebugOn)) {
3267         "a("+string(zeile+zl-2)+","+string(Q1)+") =",delta;
3268       }
3269       HNEakut[zeile+zl][Q1]=delta;
3270
3271 //--- Daten aus T2_Transform sind eingetragen; haenge Daten von HN an: -------
3272       hilfid=HNEakut[zeile+zl];
3273       for (zl1=Q1+1; zl1<=ncols(aneu[zaehler][2]); zl1++) {
3274        hilfid[zl1]=aneu[zaehler][2][zl1];
3275       }
3276       HNEakut[zeile+zl]=hilfid;
3277 //--- vorher HNEs[.][zeile+zl]<-aneu[.][2], jetzt [zeile+zl+1] <- [3] usw.: --
3278       for (zl1=3; zl1<=size(aneu[zaehler]); zl1++) {
3279         HNEakut[zeile+zl+zl1-2]=aneu[zaehler][zl1];
3280       }
3281 //--- setze die hqs zusammen: HNEs[hnezaehler][1]=HNEs[..][1],aneu[..][1] ----
3282       hilfvec=HNEakut[1],aneu[zaehler][1];
3283       HNEakut[1]=hilfvec;
3284 //----------- weil nicht geht: liste[1]=liste[1],aneu[zaehler][1] ------------
3285       HNEs[hnezaehler]=HNEakut;
3286      }                     // end(for zaehler)
3287     }                      // endelse (R<>0)
3288    }                       // endif (subst()!=0)  (weiteres Aufblasen mit HN)
3289
3290   }                        // end(for j) (Behandlung der einzelnen delta_i)
3291
3292  }
3293  keepring basering;
3294  if (defined(transfproc)) { return(list(HNEs,transfproc)); }
3295  else                     { return(list(HNEs,poly(-1))); }
3296 // -1 als 2. Rueckgabewert zeigt an, dass kein Ringwechsel stattgefunden hat -
3297 }
3298 else {
3299  HNEs[1]=list(hqs)+azeilen+list(f); // f ist das transform. Poly oder Null
3300  keepring basering;
3301  return(list(HNEs,poly(-1)));
3302 //-- in dieser proc trat keine Verzweigung auf, also auch kein Ringwechsel ---
3303 }
3304}
3305///////////////////////////////////////////////////////////////////////////////
3306
3307static proc constructHNEs (list HNEs,int hnezaehler,list aneu,list azeilen,
3308                    int zeile,ideal deltais,int Q,int j)
3309"NOTE: This procedure is only for internal use, it is called via HN"
3310{
3311  int zaehler,zl;
3312  ideal hilfid;
3313  list hilflist;
3314  intvec hilfvec;
3315  for (zaehler=1; zaehler<=size(aneu); zaehler++) {
3316     hnezaehler++;
3317     // HNEs[hnezaehler]=azeilen;            // dupliziere gemeins. Anfang
3318 //----------------------- trage neu berechnete Daten ein ---------------------
3319     hilfid=azeilen[zeile+2];
3320     hilfid[Q]=deltais[j];
3321     for (zl=Q+1; zl<=ncols(aneu[zaehler][2]); zl++) {
3322      hilfid[zl]=aneu[zaehler][2][zl];
3323     }
3324     hilflist=azeilen; hilflist[zeile+2]=hilfid;
3325 //------------------ haenge uebrige Zeilen von aneu[] an: --------------------
3326     for (zl=3; zl<=size(aneu[zaehler]); zl++) {
3327      hilflist[zeile+zl]=aneu[zaehler][zl];
3328     }
3329 //--- setze die hqs zusammen: HNEs[hnezaehler][1]=HNEs[..][1],aneu[..][1] ----
3330     if (hilflist[1]==0) { hilflist[1]=aneu[zaehler][1]; }
3331     else { hilfvec=hilflist[1],aneu[zaehler][1]; hilflist[1]=hilfvec; }
3332     HNEs[hnezaehler]=hilflist;
3333  }
3334  return(HNEs,hnezaehler);
3335}
3336///////////////////////////////////////////////////////////////////////////////
3337
3338proc referencepoly (list newton)
3339"USAGE:   referencepoly(newton);
3340         newton is list of intvec(x,y) which represents points in the Newton
3341         diagram (e.g. output of the proc newtonpoly)
3342RETURN:  a polynomial which has newton as Newton diagram
3343SEE ALSO: newtonpoly
3344EXAMPLE: example referencepoly;  shows an example
3345"
3346{
3347 poly f;
3348 for (int i=1; i<=size(newton); i++) {
3349   f=f+var(1)^newton[i][1]*var(2)^newton[i][2];
3350 }
3351 return(f);
3352}
3353example
3354{ "EXAMPLE:"; echo = 2;
3355 ring exring=0,(x,y),ds;
3356 referencepoly(list(intvec(0,4),intvec(2,3),intvec(5,1),intvec(7,0)));
3357}
3358///////////////////////////////////////////////////////////////////////////////
3359
3360proc factorlist (list L)
3361"USAGE:   factorlist(L);   L a list in the format of `factorize'
3362RETURN:  the nonconstant irreducible factors of
3363         L[1][1]^L[2][1] * L[1][2]^L[2][2] *...* L[1][size(L[1])]^...
3364         with multiplicities (same format as factorize)
3365SEE ALSO: factorize
3366EXAMPLE: example factorlist;  shows an example
3367"
3368{
3369 // eine Sortierung der Faktoren eruebrigt sich, weil keine zwei versch.
3370 // red.Fakt. einen gleichen irred. Fakt. haben koennen (I.3.27 Diplarb.)
3371 int i,gross;
3372 list faktoren,hilf;
3373 ideal hil1,hil2;
3374 intvec v,w;
3375 for (i=1; (L[1][i] == jet(L[1][i],0)) && (i<size(L[1])); i++) {;}
3376 if (L[1][i] != jet(L[1][i],0)) {
3377   hilf=factorize(L[1][i]);
3378 // Achtung!!! factorize(..,2) wirft entgegen der Beschreibung nicht nur
3379 // konstante Faktoren raus, sondern alle Einheiten in der LOKALISIERUNG nach
3380 // der Monomordnung!!! Im Beispiel unten verschwindet der Faktor x+y+1, wenn
3381 // man ds statt dp als Ordnung nimmt!
3382   hilf[2]=hilf[2]*L[2][i];
3383   hil1=hilf[1];
3384   gross=size(hil1);
3385   if (gross>1) {
3386       // faktoren=list(hilf[1][2..gross],hilf[2][2..gross]);
3387       // -->  `? indexed object must have a name'
3388     v=hilf[2];
3389     faktoren=list(ideal(hil1[2..gross]),intvec(v[2..gross]));
3390   }
3391   else         { faktoren=hilf; }
3392 }
3393 else {
3394   faktoren=L;
3395 }
3396
3397 for (i++; i<=size(L[2]); i++) {
3398 //------------------------- linearer Term -- irreduzibel ---------------------
3399   if (L[1][i] == jet(L[1][i],1)) {
3400     if (L[1][i] != jet(L[1][i],0)) {           // konst. Faktoren eliminieren
3401       hil1=faktoren[1];
3402       hil1[size(hil1)+1]=L[1][i];
3403       faktoren[1]=hil1;
3404       v=faktoren[2],L[2][i];
3405       faktoren[2]=v;
3406     }
3407   }
3408 //----------------------- nichtlinearer Term -- faktorisiere -----------------
3409   else {
3410     hilf=factorize(L[1][i]);
3411     hilf[2]=hilf[2]*L[2][i];
3412     hil1=faktoren[1];
3413     hil2=hilf[1];
3414     gross=size(hil2);
3415       // hil2[1] ist konstant, wird weggelassen:
3416     hil1[(size(hil1)+1)..(size(hil1)+gross-1)]=hil2[2..gross];
3417       // ideal+ideal does not work due to simplification;
3418       // ideal,ideal not allowed
3419     faktoren[1]=hil1;
3420     w=hilf[2];
3421     v=faktoren[2],w[2..gross];
3422     faktoren[2]=v;
3423   }
3424 }
3425 return(faktoren);
3426}
3427example
3428{ "EXAMPLE:"; echo = 2;
3429 ring exring=0,(x,y),ds;
3430 list L=ideal(x,(x-y)^2*(x+y+1),x+y),intvec(2,2,1);
3431 L;
3432 factorlist(L);
3433}
3434///////////////////////////////////////////////////////////////////////////////
3435
3436proc extrafactor (poly leitf, int M, int N)
3437"USAGE:   factors,flag=extrafactor(f,M,N);
3438         list factors, int flag,M,N, poly f in x,y
3439RETURN:  for some special f, factors is a list of the factors of
3440         charPoly(f,M,N), same format as factorize
3441         (see help charPoly; help factorize)
3442         In this case, flag!=0 (TRUE). If extrafactor cannot factorize f,
3443         flag will be 0 (FALSE), factors will be the empty list.
3444ASSUME:  basering is (0,a),(x,y),ds or ls
3445         Newton polygon of f is one side with height N, length M
3446NOTE:    This procedure is designed to make reddevelop able to compute some
3447         special cases that need a ring extension in char 0.
3448         It becomes obsolete as soon as `factorize' works also in such rings.
3449EXAMPLE: example extrafactor;  shows an example
3450"
3451{
3452 list faktoren;
3453
3454      if (a2==-1) {
3455       poly testpol=charPoly(leitf,M,N);
3456       if (testpol==1+2y2+y4) {
3457         faktoren=list(ideal(y+a,y-a),intvec(2,2));
3458         testpol=0;
3459       }
3460 //------------ ist Poly von der Form q*i+r*y^n, n in N, q,r in Q ?: ----------
3461       if ((size(testpol)==2) && (find(string(lead(testpol)),"a")>0)
3462           && (find(string(testpol-lead(testpol)),"a")==0)) {
3463        faktoren=list(ideal(testpol),intvec(1));
3464        testpol=0;
3465       }
3466      }
3467      if (a4==-625) {
3468        poly testpol=charPoly(leitf,M,N);
3469        if (testpol==4a2-4y2)
3470         { faktoren=list(ideal(-4,y+a,y-a),intvec(1,1,1)); testpol=0;}
3471        if (testpol==-4a2-4y2)
3472         { faktoren=list(ideal(-4,y+1/25*a3,y-1/25*a3),intvec(1,1,1));
3473           testpol=0;}
3474      }
3475      if (a2+a==-1) {
3476        poly testpol=charPoly(leitf,M,N);
3477        if (testpol==1+2y+3y2+2y3+y4)
3478         { faktoren=list(ideal(1,y-a,y+a+1),intvec(1,2,2)); testpol=0;}
3479      }
3480      if (defined(testpol)==0) { poly testpol=1; }
3481      if (testpol!=0) {
3482        "factorize not implemented in char (0,a)!";
3483        "could not factorize:",charPoly(leitf,M,N);
3484        if (printlevel>0) { pause("Hit RETURN to continue:"); }
3485      }
3486 return(faktoren,(testpol==0)); // Test: faktoren==list() geht leider nicht
3487}
3488example
3489{ "EXAMPLE:"; echo=2;
3490  ring r=(0,a),(x,y),ds;
3491  minpoly=a2+1;
3492  poly f=x4+2x2y2+y4;
3493  charPoly(f,4,4);
3494  list factors;
3495  int flag;
3496  factors,flag=extrafactor(f,4,4);
3497  if (flag!=0) {factors;}
3498}
Note: See TracBrowser for help on using the repository browser.