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

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