source: git/Singular/LIB/atkins.lib @ 2e553a

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