source: git/Singular/LIB/atkins.lib @ 3bef0a

fieker-DuValspielwiese
Last change on this file since 3bef0a was 1f9a84, checked in by Hans Schoenemann <hannes@…>, 13 years ago
more int division from the manual git-svn-id: file:///usr/local/Singular/svn/trunk@14203 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 32.4 KB
Line 
1///////////////////////////////////////////////////////////////////////////////
2version="$Id$";
3category="Teaching";
4info="
5LIBRARY:  atkins.lib     Procedures for teaching cryptography
6AUTHOR:                  Stefan Steidel, steidel@mathematik.uni-kl.de
7
8NOTE: The library contains auxiliary procedures to compute the elliptic
9      curve primality test of Atkin and the Atkin's Test itself.
10      The library is intended to be used for teaching purposes but not
11      for serious computations. Sufficiently high printlevel allows to
12      control each step, thus illustrating the algorithms at work.
13
14
15PROCEDURES:
16  newTest(L,D)              checks if number D already exists in list L
17  bubblesort(L)             sorts elements of the list L
18  disc(N,k)                 generates a list of negative discriminants
19  Cornacchia(d,p)           computes solution (x,y) for x^2+d*y^2=p
20  CornacchiaModified(D,p)   computes solution (x,y) for x^2+|D|*y^2=4p
21  maximum(L)                computes the maximal number contained in L
22  sqr(w,k)                  computes the square root of w w.r.t. accuracy k
23  expo(z,k)                 computes exp(z)
24  jOft(t,k)                 computes the j-invariant of t
25  round(r)                  rounds r to the nearest number out of Z
26  HilbertClassPoly(D,k)     computes the Hilbert Class Polynomial
27  rootsModp(p,P)            computes roots of the polynomial P modulo p
28  wUnit(D)                  computes the number of units in Q(sqr(D))
29  Atkin(N,K,B)              tries to prove that N is prime
30
31";
32
33LIB "crypto.lib";
34LIB "general.lib";
35LIB "ntsolve.lib";
36LIB "inout.lib";
37
38///////////////////////////////////////////////////////////////////////////////
39
40proc newTest(list L, number D)
41"USAGE: newTest(L,D);
42RETURN:  1, if D does not already exist in L,
43        -1, if D does already exist in L
44EXAMPLE:example new; shows an example
45"
46{
47  number a=1;                // a=1 means: D does not already exist in L
48  int i;
49  for(i=1;i<=size(L);i++)
50  {
51    if(D==L[i])
52    {
53      a=-1;                 // a=-1 means: D does already exist in L
54      break;
55    }
56  }
57 return(a);
58}
59example
60{ "EXAMPLE:"; echo = 2;
61    ring r = 0,x,dp;
62    list L=8976,-223456,556,-778,3,-55603,45,766677;
63    number D=-55603;
64    newTest(L,D);
65}
66
67
68proc bubblesort(list L)
69"USAGE: bubblesort(L);
70RETURN: list L, sort in decreasing order
71EXAMPLE:example bubblesort; shows an example
72"
73{
74  number b;
75  int n,i,j;
76  while(j==0)
77  {
78    i=i+1;
79    j=1;
80    for(n=1;n<=size(L)-i;n++)
81    {
82      if(L[n]<L[n+1])
83      {
84        b=L[n];
85        L[n]=L[n+1];
86        L[n+1]=b;
87        j=0;
88      }
89    }
90  }
91  return(L);
92}
93example
94{ "EXAMPLE:"; echo = 2;
95    ring r = 0,x,dp;
96    list L=-567,-233,446,12,-34,8907;
97    bubblesort(L);
98}
99
100
101proc disc(number N, int k)
102"USAGE: disc(N,k);
103RETURN: list L of negative discriminants D, sorted in decreasing order
104ASSUME: D<0, D kongruent 0 or 1 modulo 4 and |D|<4N
105NOTE:   D=b^2-4*a, where 0<=b<=k and intPart((b^2)/4)+1<=a<=k for each b
106EXAMPLE:example disc; shows an example
107"
108{
109  list L=-3,-4,-7;
110  number D;
111  number B;
112  int a,b;
113  for(b=0;b<=k;b++)
114  {
115    B=b^2;
116    for(a=int(intPart(B/4))+1;a<=k;a++)
117    {
118      D=-4*a+B;
119      if((D<0)&&((D mod 4)!=2)&&((D mod 4)!=3)&&(absValue(D)<4*N)&&(newTest(L,D)==1))
120      {
121        L[size(L)+1]=D;
122      }
123    }
124  }
125  L=bubblesort(L);
126  return(L);
127}
128example
129{ "EXAMPLE:"; echo = 2;
130    ring R = 0,x,dp;
131    disc(2003,50);
132}
133
134
135proc Cornacchia(number d, number p)
136"USAGE: Cornacchia(d,p);
137RETURN: x,y such that x^2+d*y^2=p with p prime,
138        -1, if the Diophantine equation has no solution,
139         0, if the parameters are wrong selected
140ASSUME: 0<d<p
141EXAMPLE:example Cornacchia; shows an example
142"
143{
144  if((d<0)||(p<d))              // (0)[Test if assumptions well-defined]
145  {
146    return(0);
147    // ERROR("Parameters wrong selected! It has to be 0<d<p!");
148  }
149  else
150  {
151    number k,x(0),a,b,l,r,c,i;
152
153    k=Jacobi(-d,p);             // (1)[Test if residue]
154    if(k==-1)
155    {
156      return(-1);
157      // ERROR("The Diophantine equation has no solution!");
158    }
159    else
160    {
161       x(0)=squareRoot(-d,p);   // (2)[Compute square root]
162       if((p/2>=x(0))||(p<=x(0)))
163       {
164           x(0)=-x(0) mod p;
165       }
166       a=p;
167       b=x(0);
168       l=intRoot(p);
169       while(b>l)               // (3)[Euclidean algorithm]
170       {
171          r=a mod b;
172          a=b;
173          b=r;
174       }
175       c=(p-b^2)/d;             // (4)[Test solution]
176       i=intRoot(c);
177       if((((p-b^2) mod d)!=0)||(c!=i^2))
178       {
179          return(-1);
180       }
181       else
182       {
183          list L=b,i;
184          return(L);
185       }
186    }
187  }
188}
189example
190{ "EXAMPLE:"; echo = 2;
191    ring R = 0,x,dp;
192    Cornacchia(55,9551);
193}
194
195
196proc CornacchiaModified(number D, number p)
197"USAGE: CornacchiaModified(D,p);
198RETURN: x,y such that x^2+|D|*y^2=p with p prime,
199        -1, if the Diophantine equation has no solution,
200         0, if the parameters are wrong selected
201ASSUME: D<0, D kongruent 0 or 1 modulo 4 and |D|<4p
202EXAMPLE:example CornacchiaModified; shows an example
203"
204{
205  if((D>=0)||((D mod 4)==2)||((D mod 4)==3)||(absValue(D)>=4*p))
206  {                                  // (0)[Test if assumptions well-defined]
207    return(0);
208    // ERROR("Parameters wrong selected!");
209  }
210  else
211  {
212    if(p==2)                         // (1)[Case p=2]
213    {
214      if((D+8)==intRoot(D+8)^2)
215      {
216        return(intRoot(D+8),1);
217      }
218      else
219      {
220        return(-1);
221        // ERROR("The Diophantine equation has no solution!");
222      }
223    }
224    else
225    {
226      number k,x(0),a,b,l,r,c;
227      k=Jacobi(D,p);                 // (2)[Test if residue]
228      if(k==-1)
229      {
230        return(-1);
231        // ERROR("The Diophantine equation has no solution!");
232      }
233      else
234      {
235        x(0)=squareRoot(D,p);        // (3)[Compute square root]
236        if((x(0) mod 2)!=(D mod 2))
237        {
238          x(0)=p-x(0);
239        }
240        a=2*p;
241        b=x(0);
242        l=intRoot(4*p);
243        while(b>l)                   // (4)[Euclidean algorithm]
244        {
245          r=a mod b;
246          a=b;
247          b=r;
248        }
249        c=(4*p-b^2)/absValue(D);     // (5)[Test solution]
250        if((((4*p-b^2) mod absValue(D))!=0)||(c!=intRoot(c)^2))
251        {
252          return(-1);
253          // ERROR("The Diophantine equation has no solution!");
254        }
255        else
256        {
257          list L=b,intRoot(c);
258          return(L);
259        }
260      }
261    }
262  }
263}
264example
265{ "EXAMPLE:"; echo = 2;
266    ring R = 0,x,dp;
267    CornacchiaModified(-107,1319);
268}
269
270
271proc pFactor1(number n,int B, list P)
272"USAGE: pFactor1(n,B,P); n to be factorized, B a bound , P a list of primes
273RETURN: a list of factors of n or the message: no factor found
274NOTE:   Pollard's p-factorization
275        creates the product k of powers of primes (bounded by B)  from
276        the list P with the idea that for a prime divisor p of n p-1|k
277        then p devides gcd(a^k-1,n) for some random a
278EXAMPLE:example pFactor1; shows an example
279"
280{
281  int i;
282  number k=1;
283  number w;
284  while(i<size(P))
285  {
286    i++;
287    w=P[i];
288    if(w>B) {break;}
289    while(w*P[i]<=B)
290    {
291      w=w*P[i];
292    }
293    k=k*w;
294  }
295  number a=random(2,2147483629);
296  number d=gcdN(powerN(a,k,n)-1,n);
297  if((d>1)&&(d<n)){return(d);}
298  return(n);
299}
300example
301{ "EXAMPLE:"; echo = 2;
302   ring R = 0,z,dp;
303   list L=primList(1000);
304   pFactor1(1241143,13,L);
305   number h=10;
306   h=h^30+25;
307   pFactor1(h,20,L);
308}
309
310
311proc maximum(list L)
312"USAGE: maximum(list L);
313RETURN: the maximal number contained in list L
314EXAMPLE:example maximum; shows an example
315"
316{
317  number max=L[1];
318  int i;
319  for(i=2;i<=size(L);i++)
320  {
321    if(L[i]>max)
322    {
323      max=L[i];
324    }
325  }
326  return(max);
327}
328example
329{ "EXAMPLE:"; echo = 2;
330    ring r = 0,x,dp;
331    list L=465,867,1233,4567,776544,233445,2334,556;
332    maximum(L);
333}
334
335
336static proc cmod(number x, number y)
337"USAGE: cmod(x,y);
338RETURN: x mod y
339ASSUME: x,y out of Z and x,y<=2147483647
340NOTE:   this algorithm is a helping procedure to be able to calculate
341        x mod y with x,y out of Z while working in the complex field
342EXAMPLE:example cmod; shows an example
343"
344{
345  int rest=int(x-y*int(x/y));
346  if(rest<0)
347  {
348    rest=rest+int(y);
349  }
350  return(rest);
351}
352example
353{ "EXAMPLE:"; echo = 2;
354    ring r = (complex,30,i),x,dp;
355    number x=-1004456;
356    number y=1233;
357    cmod(x,y);
358}
359
360
361proc sqr(number w, int k)
362"USAGE: sqr(w,k);
363RETURN: the square root of w
364ASSUME: w>=0
365NOTE:   k describes the number of decimals being calculated in the real numbers,
366        k, intPart(k/5) are inputs for the procedure "nt_solve"
367EXAMPLE:example sqr; shows an example
368"
369{
370  poly f=var(1)^2-w;
371  def S=basering;
372  ring R=(real,k),var(1),dp;
373  poly f=imap(S,f);
374  ideal I=nt_solve(f,1.1,list(k,k div 5));
375  number c=leadcoef(I[1]);
376  setring S;
377  number c=imap(R,c);
378  return(c);
379}
380example
381{ "EXAMPLE:"; echo = 2;
382    ring R = (real,60),x,dp;
383    number ww=288469650108669535726081;
384    sqr(ww,60);
385}
386
387
388proc expo(number z, int k)
389"USAGE: expo(z,k);
390RETURN: e^z to the order k
391NOTE:   k describes the number of summands being calculated in the exponential power series
392EXAMPLE:example expo; shows an example
393"
394{
395  number q=1;
396  number e=1;
397  int n;
398  for(n=1;n<=k;n++)
399  {
400    q=q*z/n;
401    e=e+q;
402  }
403  return(e);
404}
405example
406{ "EXAMPLE:"; echo = 2;
407    ring r = (real,30),x,dp;
408    number z=40.35;
409    expo(z,1000);
410}
411
412
413proc jOft(number t, int k)
414"USAGE: jOft(t,k);
415RETURN: the j-invariant of t
416ASSUME: t is a complex number with positive imaginary part
417NOTE:   k describes the number of summands being calculated in the power series,
418        10*k is input for the procedure @code{expo}
419EXAMPLE:example jOft; shows an example
420"
421{
422  number q1,q2,qr1,qi1,tr,ti,m1,m2,f,j;
423
424  number pi=3.1415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253421170679821480865132823066470938446095505822317253594081284811174502841027019385211055596446229489549303819644288109756659334461284756482337867831652712019091456485669234603486104543266482133936072602491412737245870066063155881748815209209628292540917153643678925903600113305305488204665213841469519415116094330572703657595919530921861173819326117931051185480744623799627495673518857527248912279381830119491298336733624406566430860213949463952247371907021798609437027705392171762931767523846748184676694051320005681271452635608277857713427577896091736371787214684409012249534301465495853710507922796892589235420199561121290219608640344181598136297747713099605187072113499999983729780499510597317328160963185950244594553469083026425223082533446850352619311881710100031378387528865875332083814206171776691473035982534904287554687311595628638823537875937519577818577805321712268066130019278766111959092164201989;
425
426  tr=repart(t);
427  ti=impart(t);
428  if(tr==-1/2){qr1=-1;}
429  else
430  {
431    if(tr==0){qr1=1;}
432    else
433    {
434      tr=tr-round(tr);
435      qr1=expo(2*i*pi*tr,10*k);
436    }
437  }
438
439  qi1=expo(-pi*ti,10*k);
440  q1=qr1*qi1^2;
441  q2=q1^2;
442
443  int n=1;
444  while(n<=k)
445  {
446    m1=m1+(-1)^n*(q1^(n*(3*n-1) div 2)+q1^(n*(3*n+1) div 2));
447    m2=m2+(-1)^n*(q2^(n*(3*n-1) div 2)+q2^(n*(3*n+1) div 2));
448    n++;
449  }
450
451  f=q1*((1+m2)/(1+m1))^24;
452
453  j=(256*f+1)^3/f;
454  return(j);
455}
456example
457{ "EXAMPLE:"; echo = 2;
458    ring r = (complex,30,i),x,dp;
459    number t=(-7+i*sqr(7,250))/2;
460    jOft(t,50);
461}
462
463
464proc round(number r)
465"USAGE: round(r);
466RETURN: the nearest number to r out of Z
467ASSUME: r should be a rational or a real number
468EXAMPLE:example round; shows an example
469"
470{
471  number a=absValue(r);
472  number v=r/a;
473
474  number d=10;
475  int e;
476  while(1)
477  {
478    e=e+1;
479    if(a-d^e<0)
480    {
481      e=e-1;
482      break;
483    }
484  }
485
486  number b=a;
487  int k;
488  for(k=0;k<=e;k++)
489  {
490    while(1)
491    {
492      b=b-d^(e-k);
493      if(b<0)
494      {
495        b=b+d^(e-k);
496        break;
497      }
498    }
499  }
500
501  if(b<1/2)
502  {
503    return(v*(a-b));
504  }
505  else
506  {
507    return(v*(a+1-b));
508  }
509}
510example
511{ "EXAMPLE:"; echo = 2;
512    ring R = (real,50),x,dp;
513    number r=7357683445788723456321.6788643224;
514    round(r);
515}
516
517
518proc HilbertClassPoly(number D, int k)
519"USAGE: HilbertClassPoly(D,k);
520RETURN: the monic polynomial of degree h(D) in Z[X] of which jOft((D+sqr(D))/2) is a root
521ASSUME: D is a negative discriminant
522NOTE:   k is input for the procedure "jOft",
523        5*k is input for the procedure "sqr",
524        10*k describes the number of decimals being calculated in the complex numbers
525EXAMPLE:example HilbertClassPoly; shows an example
526"
527{
528  if(D>=0)                     // (0)[Test if assumptions well-defined]
529  {
530    ERROR("Parameter wrong selected!");
531  }
532  else
533  {
534    def S=basering;
535    ring R=0,x,dp;
536
537    string s1,s2,s3;
538    number a1,b1,t1,g1;
539    number D=imap(S,D);
540    number B=intRoot(absValue(D)/3);
541
542    ring C=(complex,10*k,i),x,dp;
543    number D=imap(S,D);
544
545    poly P=1;                  // (1)[Initialize]
546    number b=cmod(D,2);
547    number B=imap(R,B);
548
549    number t,a,g,tau,j;
550    list L;
551
552    int step=2;
553    while(1)
554    {
555      if(step==2)              // (2)[Initialize a]
556      {
557        t=(b^2-D)/4;
558        L=b,1;
559        a=maximum(L);
560        step=3;
561      }
562
563      if(step==3)              // (3)[Test]
564      {
565        if((cmod(t,a)!=0))
566        {
567          step=4;
568        }
569        else
570        {
571          s1=string(a);
572          s2=string(b);
573          s3=string(t);
574
575          setring R;
576          execute("a1="+s1+";");
577          execute("b1="+s2+";");
578          execute("t1="+s3+";");
579          g1=gcd(gcd(a1,b1),t1/a1);
580          setring C;
581          g=imap(R,g1);
582
583          if(g!=1)
584          {
585            step=4;
586          }
587          else
588          {
589            tau=(-b+i*sqr(absValue(D),5*k))/(2*a);
590            j=jOft(tau,k);
591            if((a==b)||(a^2==t)||(b==0))
592            {
593              P=P*(var(1)-repart(j));
594              step=4;
595            }
596            else
597            {
598              P=P*(var(1)^2-2*repart(j)*var(1)+repart(j)^2+impart(j)^2);
599              step=4;
600            }
601          }
602        }
603      }
604
605      if(step==4)              // (4)[Loop on a]
606      {
607        a=a+1;
608        if(a^2<=t)
609        {
610          step=3;
611          continue;
612        }
613        else
614        {
615          step=5;
616        }
617      }
618
619      if(step==5)              // (5)[Loop on b]
620      {
621        b=b+2;
622        if(b<=B)
623        {
624          step=2;
625        }
626        else
627        {
628          break;
629        }
630      }
631    }
632
633    matrix M=coeffs(P,var(1));
634
635    list liste;
636    int n;
637    for(n=1;n<=nrows(M);n++)
638    {
639      liste[n]=round(repart(number(M[n,1])));
640    }
641
642    poly Q;
643    int m;
644    for(m=1;m<=size(liste);m++)
645    {
646      Q=Q+liste[m]*var(1)^(m-1);
647    }
648
649    string s=string(Q);
650    setring S;
651    execute("poly Q="+s+";");
652    return(Q);
653  }
654}
655example
656{ "EXAMPLE:"; echo = 2;
657    ring r = 0,x,dp;
658    number D=-23;
659    HilbertClassPoly(D,50);
660}
661
662
663proc rootsModp(int p, poly P)
664"USAGE: rootsModp(p,P);
665RETURN: list of roots of the polynomial P modulo p with p prime
666ASSUME: p>=3
667NOTE:   this algorithm will be called recursively, and it is understood
668        that all the operations are done in Z/pZ (excepting squareRoot(d,p))
669EXAMPLE:example rootsModp; shows an example
670"
671{
672  if(p<3)                                 // (0)[Test if assumptions well-defined]
673  {
674    ERROR("Parameter wrong selected, since p<3!");
675  }
676  else
677  {
678    def S=basering;
679    ring R=p,var(1),dp;
680
681    poly P=imap(S,P);
682    number d;
683    int a;
684    list L;
685
686    poly A=gcd(var(1)^p-var(1),P);        // (1)[Isolate roots in Z/pZ]
687    if(subst(A,var(1),0)==0)
688    {
689      L[1]=0;
690      A=A/var(1);
691    }
692
693    if(deg(A)==0)                         // (2)[Small degree?]
694    {
695      return(L);
696    }
697
698    if(deg(A)==1)
699    {
700      matrix M=coeffs(A,var(1));
701      L[size(L)+1]=-leadcoef(M[1,1])/leadcoef(M[2,1]);
702      setring S;
703      list L=imap(R,L);
704      return(L);
705    }
706
707    if(deg(A)==2)
708    {
709      matrix M=coeffs(A,var(1));
710      d=leadcoef(M[2,1])^2-4*leadcoef(M[1,1])*leadcoef(M[3,1]);
711
712      ring T=0,var(1),dp;
713      number d=imap(R,d);
714      number e=squareRoot(d,p);
715      setring R;
716      number e=imap(T,e);
717
718      L[size(L)+1]=(-leadcoef(M[2,1])+e)/(2*leadcoef(M[3,1]));
719      L[size(L)+1]=(-leadcoef(M[2,1])-e)/(2*leadcoef(M[3,1]));
720      setring S;
721      list L=imap(R,L);
722      return(L);
723    }
724
725    poly B=1;                             // (3)[Random splitting]
726    poly C;
727    while((deg(B)==0)||(deg(B)==deg(A)))
728    {
729      a=random(0,p-1);
730      B=gcd((var(1)+a)^((p-1) div 2)-1,A);
731      C=A/B;
732    }
733
734    setring S;                            // (4)[Recurse]
735    poly B=imap(R,B);
736    poly C=imap(R,C);
737    list l=L+rootsModp(p,B)+rootsModp(p,C);
738    return(l);
739  }
740}
741example
742{ "EXAMPLE:"; echo = 2;
743    ring r = 0,x,dp;
744    poly f=x4+2x3-5x2+x;
745    rootsModp(7,f);
746    poly g=x5+112x4+655x3+551x2+1129x+831;
747    rootsModp(1223,g);
748}
749
750
751proc wUnit(number D)
752"USAGE: wUnit(D);
753RETURN: the number of roots of unity in the quadratic order of discriminant D
754ASSUME: D<0 a discriminant kongruent to 0 or 1 modulo 4
755EXAMPLE:example w; shows an example
756"
757{
758  if((D>=0)||((D mod 4)==2)||((D mod 4)==3))
759  {
760    ERROR("Parameter wrong selected!");
761  }
762  else
763  {
764    if(D<-4) {return(2);}
765    if(D==-4){return(4);}
766    if(D==-3){return(6);}
767  }
768}
769example
770{ "EXAMPLE:"; echo = 2;
771    ring r = 0,x,dp;
772    number D=-3;
773    wUnit(D);
774}
775
776
777proc Atkin(number N, int K, int B)
778"USAGE: Atkin(N,K,B);
779RETURN:  1, if N is prime,
780        -1, if N is not prime,
781         0, if the algorithm is not applicable, since there are too few discriminants
782ASSUME: N is coprime to 6 and different from 1
783NOTE:   K/2 is input for the procedure "disc",@*
784        K is input for the procedure "HilbertClassPoly",@*
785        B describes the number of recursions being calculated.@*
786        The basis of the algorithm is the following theorem:
787          Let N be an integer coprime to 6 and different from 1 and E be an
788          ellipic curve modulo N.@* Assume that we know an integer m and a
789          point P of E(Z/NZ) satisfying the following conditions.@*
790           (1) There exists a prime divisor q of m such that q > (4-th root(N)+1)^2.@*
791           (2) m*P = O(E) = (0:1:0).@*
792           (3) (m/q)*P = (x:y:t) with t element of (Z/NZ)*.@*
793          Then N is prime.
794EXAMPLE:example Atkin; shows an example
795"
796{
797  if(N==1)           {return(-1);} // (0)[Test if assumptions well-defined]
798  if((N==2)||(N==3)) {return(1);}
799  if(gcdN(N,6)!=1)
800  {
801    if(printlevel>=1) {"gcd(N,6) = "+string(gcdN(N,6));pause();"";}
802    return(-1);
803  }
804  else
805  {
806    int i;                         // (1)[Initialize]
807    int n(i);
808    number N(i)=N;
809    if(printlevel>=1) {"Set i = 0, n = 0 and N(i) = N(0)= "+string(N(i))+".";pause();"";}
810
811    // declarations:
812    int j(0),j(1),j(2),j(3),j(4),k;    // running indices
813    list L;                            // all primes smaller than 1000
814    list H;                            // sequence of negative discriminants
815    number D;                          // discriminant out of H
816    list L1,L2,S,S1,S2,R;              // lists of relevant elements
817    list P,P1,P2;                      // elliptic points on E(Z/N(i)Z)
818    number m,q;                        // m=|E(Z/N(i)Z)| and q|m
819    number a,b,j,c;                    // characterize E(Z/N(i)Z)
820    number g,u;                        // g out of Z/N(i)Z, u=Jacobi(g,N(i))
821    poly T;                            // T=HilbertClassPoly(D,K)
822    matrix M;                          // M contains the coefficients of T
823
824    if(printlevel>=1) {"List H of possibly suitable discriminants will be calculated.";}
825    H=disc(N,K div 2);
826    if(printlevel>=1) {"H = "+string(H);pause();"";}
827
828    int step=2;
829    while(1)
830    {
831      if(step==2)                  // (2)[Is N(i) small??]
832      {
833        L=5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73,79,83,89,97,101,103,107,109,113,127,131,137,139,149,151,157,163,167,173,179,181,191,193,197,199,211,223,227,229,233,239,241,251,257,263,269,271,277,281,283,293,307,311,313,317,331,337,347,349,353,359,367,373,379,383,389,397,401,409,419,421,431,433,439,443,449,457,461,463,467,479,487,491,499,503,509,521,523,541,547,557,563,569,571,577,587,593,599,601,607,613,617,619,631,641,643,647,653,659,661,673,677,683,691,701,709,719,727,733,739,743,751,757,761,769,773,787,797,809,811,821,823,827,829,839,853,857,859,863,877,881,883,887,907,911,919,929,937,941,947,953,967,971,977,983,991,997;
834        for(j(0)=1;j(0)<=size(L);j(0)++)
835        {
836          if(N(i)==L[j(0)]){return(1);}
837          if(((N(i) mod L[j(0)])==0)&&(N(i)!=L[j(0)]))
838          {
839            if(printlevel>=1) {"N("+string(i)+") = "+string(N(i))+" is divisible by "+string(L[j(0)])+".";pause();"";}
840            step=14;
841            break;
842          }
843        }
844        if(step==2)
845        {
846          step=3;
847        }
848      }
849
850      if(step==3)                  // (3)[Choose next discriminant]
851      {
852        n(i)=n(i)+1;
853        if(n(i)==size(H)+1)
854        {
855          if(printlevel>=1) {"Algorithm is not applicable, since there are not enough suitable discriminants.";
856                             "Increase the parameter of accuracy K and start the algorithm again.";pause();"";}
857          return(0);
858        }
859        D=H[n(i)];
860        if(printlevel>=1) {"Next discriminant D will be chosen. D = "+string(D)+".";pause();"";}
861        if(Jacobi(D,N(i))!=1)
862        {
863          if(printlevel>=1) {"Jacobi(D,N("+string(i)+")) = "+string(Jacobi(D,N(i)));pause();"";}
864          continue;
865        }
866        else
867        {
868          L1=CornacchiaModified(D,N(i));
869          if(size(L1)>1)
870          {
871            if(printlevel>=1) {"The solution (x,y) of the equation x^2+|D|y^2 = 4N("+string(i)+") is";L1;pause();"";}
872            step=4;
873          }
874          else
875          {
876            if(L1[1]==-1)
877            {
878              if(printlevel>=1) {"The equation x^2+|D|y^2 = 4N("+string(i)+") has no solution.";pause();"";}
879              continue;
880            }
881            if(L1[1]==0)
882            {
883              if(printLevel>=1) {"Algorithm is not applicable for N("+string(i)+") = "+string(N(i))+",";
884                                 "since there are not enough suitable discriminants.";pause();"";}
885              step=14;
886            }
887          }
888        }
889      }
890
891      if(step==4)                  // (4)[Factor m]
892      {
893        if(printlevel>=1) {"List L2 of possible m = |E(Z/N("+string(i)+")Z)| will be calculated.";}
894        if(absValue(L1[1])^2<=4*N(i)) {L2=N(i)+1+L1[1],N(i)+1-L1[1];}
895        if(D==-4)
896        {
897          if(absValue(2*L1[2])^2<=4*N(i)) {L2[size(L2)+1]=N(i)+1+2*L1[2];
898                                           L2[size(L2)+1]=N(i)+1-2*L1[2];}
899        }
900// At this point "<=4*N(i)" has been replaced by "<=16*N(i)".
901        if(D==-3)
902        {
903          if(absValue(L1[1]+3*L1[2])^2<=16*N(i)) {L2[size(L2)+1]=N(i)+1+(L1[1]+3*L1[2])/2;
904                                                  L2[size(L2)+1]=N(i)+1-(L1[1]+3*L1[2])/2;}
905          if(absValue(L1[1]-3*L1[2])^2<=16*N(i)) {L2[size(L2)+1]=N(i)+1+(L1[1]-3*L1[2])/2;
906                                                  L2[size(L2)+1]=N(i)+1-(L1[1]-3*L1[2])/2;}
907        }
908///////////////////////////////////////////////////////////////
909        if(size(L2)==0)
910        {
911          if(printlevel>=1) {"Due to the theorem of Hasse there were no possible m = |E(Z/N("+string(i)+")Z)|";
912                             "found for D = "+string(D)+".";}
913          step=3;
914          continue;
915        }
916        else
917        {
918          if(printlevel>=1) {"L2 = ";L2;pause();"";}
919        }
920
921        if(printlevel>=1) {"List S of factors of all possible m will be calculated.";}
922        S=list();
923        for(j(1)=1;j(1)<=size(L2);j(1)++)
924        {
925          m=L2[j(1)];
926          if(m!=0)
927          {
928            S1=PollardRho(m,10000,1,L);
929            S2=pFactor(m,100,L);
930            S[size(S)+1]=list(m,S1+S2);
931          }
932        }
933        if(printlevel>=1) {"S=";S;pause();"";}
934        step=5;
935      }
936
937      if(step==5)                  // (5)[Does a suitable m exist??]
938      {
939        for(j(2)=1;j(2)<=size(S);j(2)++)
940        {
941          m=L2[j(2)];
942          for(j(3)=1;j(3)<=size(S[j(2)][2]);j(3)++)
943          {
944            q=S[j(2)][2][j(3)];
945// sqr(sqr(N(i),50),50) replaces intRoot(intRoot(N(i)))
946            if((q>(sqr(sqr(N(i),50),50)+1)^2) && (MillerRabin(q,5)==1))
947            {
948              step=6;
949              break;
950            }
951//////////////////////////////////////////////////////
952          }
953          if(step==6)
954          {
955            if(printlevel>=1) {"Suitable pair (m,q) has been found such that q|m,";
956                               "q > (4-th root(N("+string(i)+"))+1)^2 and q passes the Miller-Rabin-Test.";
957                               "m = "+string(m)+",";"q = "+string(q);pause();"";}
958            break;
959          }
960          else
961          {
962            step=3;
963          }
964        }
965        if(step==3)
966        {
967          if(printlevel>=1) {"No suitable pair (m,q) has been found such that q|m,";
968                             "q > (4-th root(N("+string(i)+"))+1)^2 and q passes the Miller-Rabin-Test.";
969                              pause();"";}
970          continue;
971        }
972      }
973
974      if(step==6)                  // (6)[Compute elliptic curve]
975      {
976        if(D==-4)
977        {
978          a=-1;
979          b=0;
980          if(printlevel>=1) {"Since D = -4, set a = -1 and b = 0.";pause();"";}
981        }
982        if(D==-3)
983        {
984          a=0;
985          b=-1;
986          if(printlevel>=1) {"Since D = -3, set a = 0 and b = -1.";pause();"";}
987        }
988        if(D<-4)
989        {
990          if(printlevel>=1) {"The minimal polynomial T of j((D+sqr(D))/2) in Z[X] will be calculated for D="+string(D)+".";}
991          T=HilbertClassPoly(D,K);
992          if(printlevel>=1) {"T = "+string(T);pause();"";}
993
994          M=coeffs(T,var(1));
995          T=0;
996
997          for(j(4)=1;j(4)<=nrows(M);j(4)++)
998          {
999            M[j(4),1]=leadcoef(M[j(4),1]) mod N(i);
1000            T=T+M[j(4),1]*var(1)^(j(4)-1);
1001          }
1002          if(printlevel>=1) {"Set T = T mod N("+string(i)+").";"T = "+string(T);pause();"";}
1003
1004          R=rootsModp(int(N(i)),T);
1005          if(deg(T)>size(R))
1006          {
1007            ERROR("The polynomial T does not completely split into linear factors modulo N("+string(i)+")."
1008                  "Increase the parameter of accuracy K and start the algorithm again.");
1009          }
1010          if(printlevel>=1) {if(deg(T)>1) {"The "+string(deg(T))+" zeroes of T modulo N("+string(i)+") are";
1011                                           R;pause();"";}
1012                             if(deg(T)==1){"The zero of T modulo N("+string(i)+") is";R;pause();"";}}
1013
1014          j=R[1];
1015          c=j*exgcdN(j-1728,N(i))[1];
1016          a=-3*c mod N(i);
1017          b=2*c mod N(i);
1018          if(printlevel>=1) {"Choose the zero j = "+string(j)+" and set"; "c = j/(j-1728) mod N("+string(i)+"), a = -3c mod N("+string(i)+"), b = 2c mod N("+string(i)+").";
1019                             "a = "+string(a)+",";"b = "+string(b);pause();"";}
1020        }
1021        step=7;
1022      }
1023
1024      if(step==7)                  // (7)[Find g]
1025      {
1026        if(D==-3)
1027        {
1028          while(1)
1029          {
1030            g=random(1,2147483647) mod N(i);
1031            u=Jacobi(g,N(i));
1032            if((u==-1)&&(powerN(g,(N(i)-1)/3,N(i))!=1))
1033            {
1034              if(printlevel>=1) {"g = "+string(g);pause();"";}
1035              break;
1036            }
1037          }
1038        }
1039        else
1040        {
1041          while(1)
1042          {
1043            g=random(1,2147483647) mod N(i);
1044            u=Jacobi(g,N(i));
1045            if(u==-1)
1046            {
1047              if(printlevel>=1) {"g = "+string(g);pause();"";}
1048              break;
1049            }
1050          }
1051        }
1052        step=8;
1053      }
1054
1055      if(step==8)                  // (8)[Find P]
1056      {
1057        if(printlevel>=1) {"A random point P on the elliptic curve corresponding";
1058                           "to the equation y^2 = x^3+ax+b for";"N("+string(i)+") = "+string(N(i))+",";
1059                           "   a = "+string(a)+",";"   b = "+string(b);"will be chosen.";}
1060        P=ellipticRandomPoint(N(i),a,b);
1061        if(printlevel>=1) {"P = ("+string(P)+")";pause();"";}
1062
1063        if(size(P)==1)
1064        {
1065          step=14;
1066        }
1067        else
1068        {
1069          step=9;
1070        }
1071      }
1072
1073      if(step==9)                  // (9)[Find right curve]
1074      {
1075        if(printlevel>=1) {"The points P2 = (m/q)*P and P1 = q*P2 on the curve will be calculated.";}
1076        P2=ellipticMult(N(i),a,b,P,m/q);
1077        P1=ellipticMult(N(i),a,b,P2,q);
1078        if(printlevel>=1) {"P1 = ("+string(P1)+"),";"P2 = ("+string(P2)+")";pause();"";}
1079
1080        if((P1[1]==0)&&(P1[2]==1)&&(P1[3]==0))
1081        {
1082          step=12;
1083        }
1084        else
1085        {
1086          if(printlevel>=1) {"Since P1 != (0:1:0), it holds m != |E(Z/N("+string(i)+")Z)| for the coefficients a = "+string(a)+" and b = "+string(b)+".";
1087                             "Therefore choose new coefficients a and b.";pause();"";}
1088          step=10;
1089        }
1090      }
1091
1092      if(step==10)                 // (10)[Change coefficients]
1093      {
1094        k=k+1;
1095        if(k>=wUnit(D))
1096        {
1097          if(printlevel>=1) {"Since k = wUnit(D) = "+string(k)+", it holds that N("+string(i)+") = "+string(N(i))+" is not prime.";pause();"";}
1098          step=14;
1099        }
1100        else
1101        {
1102          if(D<-4) {a=a*g^2 mod N(i); b=b*g^3 mod N(i);
1103                    if(printlevel>=1) {"Since D < -4, set a = a*g^2 mod N("+string(i)+") and b = b*g^3 mod N("+string(i)+").";
1104                                       "a = "+string(a)+",";"b = "+string(b)+",";"k = "+string(k);pause();"";}}
1105          if(D==-4){a=a*g mod N(i);
1106                    if(printlevel>=1) {"Since D = -4, set a = a*g mod N("+string(i)+").";"a = "+string(a)+",";
1107                                       "b = "+string(b)+",";"k = "+string(k);pause();"";}}
1108          if(D==-3){b=b*g mod N(i);
1109                    if(printlevel>=1) {"Since D = -3, set b = b*g mod N("+string(i)+").";"a = "+string(a)+",";
1110                                       "b = "+string(b)+",";"k = "+string(k);pause();"";}}
1111          step=8;
1112          continue;
1113        }
1114      }
1115
1116      if(step==11)                 // (11)[Find a new P]
1117      {
1118        if(printlevel>=1) {"A new random point P on the elliptic curve will be chosen,";
1119                           "since also P2 = (0:1:0).";}
1120        P=ellipticRandomPoint(N(i),a,b);
1121        if(printlevel>=1) {"P = ("+string(P)+")";pause();"";}
1122
1123        if(size(P)==1)
1124        {
1125          step=14;
1126        }
1127        else
1128        {
1129          if(printlevel>=1) {"The points P2 = (m/q)*P and P1 = q*P2 on the curve will be calculated.";}
1130          P2=ellipticMult(N(i),a,b,P,m/q);
1131          P1=ellipticMult(N(i),a,b,P2,q);
1132          if(printlevel>=1) {"P1 = ("+string(P1)+"),";"P2 = ("+string(P2)+")";pause();"";}
1133
1134          if((P1[1]!=0)||(P1[2]!=1)||(P1[3]!=0))
1135          {
1136            if(printlevel>=1) {"Since P1 != (0:1:0), it holds m != |E(Z/N("+string(i)+")Z)| for the coefficients a = "+string(a)+" and b = "+string(b)+".";
1137                               "Therefore choose new coefficients a and b.";pause();"";}
1138            step=10;
1139            continue;
1140          }
1141          else
1142          {
1143            step=12;
1144          }
1145        }
1146      }
1147
1148      if(step==12)                 // (12)[Check P]
1149      {
1150        if((P2[1]==0)&&(P2[2]==1)&&(P2[3]==0))
1151        {
1152          step=11;
1153          continue;
1154        }
1155        else
1156        {
1157          step=13;
1158        }
1159      }
1160
1161      if(step==13)                 // (13)[Recurse]
1162      {
1163        if(i<B)
1164        {
1165          if(printlevel>=1) {string(i+1)+". Recursion:";"";
1166                             "N("+string(i)+") = "+string(N(i))+" suffices the conditions of the underlying theorem,";
1167                             "since P1 = (0:1:0) and P2[3] in (Z/N("+string(i)+")Z)*.";"";
1168                             "Now check if also the found factor q="+string(q)+" suffices these assumptions.";
1169                             "Therefore set i = i+1, N("+string(i+1)+") = q = "+string(q)+" and restart the algorithm.";pause();"";}
1170          i=i+1;
1171          int n(i);
1172          number N(i)=q;
1173          k=0;
1174          step=2;
1175          continue;
1176        }
1177        else
1178        {
1179          if(printlevel>=1) {"N(B) = N("+string(i)+") = "+string(N(i))+" suffices the conditions of the underlying theorem,";
1180                             "since P1 = (0:1:0) and P2[3] in (Z/N("+string(i)+")Z)*.";
1181                             "In particular N = "+string(N)+" is prime.";pause();"";}
1182          return(1);
1183        }
1184      }
1185
1186      if(step==14)                 // (14)[Backtrack]
1187      {
1188        if(i>0)
1189        {
1190          if(printlevel>=1) {"Set i = i-1 and restart the algorithm for N("+string(i-1)+") = "+string(N(i-1))+" with";
1191                             "a new discriminant.";pause();"";}
1192          i=i-1;
1193          k=0;
1194          step=3;
1195        }
1196        else
1197        {
1198          if(printlevel>=1) {"N(0) = N = "+string(N)+" and therefore N is not prime.";pause();"";}
1199          return(-1);
1200        }
1201      }
1202    }
1203  }
1204}
1205example
1206{ "EXAMPLE:"; echo = 2;
1207    ring R = 0,x,dp;
1208    Atkin(7691,100,5);
1209    Atkin(3473,10,2);
1210    printlevel=1;
1211    Atkin(10000079,100,2);
1212}
1213
Note: See TracBrowser for help on using the repository browser.