source: git/Singular/LIB/hnoether.lib @ 50cbdc

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