[BACK]Return to compat CVS log [TXT][DIR] Up to [local] / OpenXM_contrib / pari-2.2 / src / test / in

Annotation of OpenXM_contrib/pari-2.2/src/test/in/compat, Revision 1.2

1.1       noro        1: \e
                      2: default(compatible,3)
                      3: +3
                      4: -5
                      5: 5+3
                      6: 5-3
                      7: 5/3
                      8: 5\3
                      9: 5\/3
                     10: 5%3
                     11: 5^3
                     12: \precision=57
                     13: pi
                     14: \precision=38
                     15: o(x^12)
                     16: padicno=(5/3)*127+O(127^5)
                     17: initrect(0,500,500)
                     18: \\ A
                     19: abs(-0.01)
                     20: acos(0.5)
                     21: acosh(3)
                     22: acurve=initell([0,0,1,-1,0])
                     23: apoint=[2,2]
                     24: isoncurve(acurve,apoint)
                     25: addell(acurve,apoint,apoint)
                     26: addprimes([nextprime(10^9),nextprime(10^10)])
                     27: adj([1,2;3,4])
                     28: agm(1,2)
                     29: agm(1+o(7^5),8+o(7^5))
                     30: algdep(2*cos(2*pi/13),6)
                     31: algdep2(2*cos(2*pi/13),6,15)
                     32: \\allocatemem(3000000)
                     33: akell(acurve,1000000007)
                     34: nfpol=x^5-5*x^3+5*x+25
                     35: nf=initalg(nfpol)
                     36: ba=algtobasis(nf,mod(x^3+5,nfpol))
                     37: anell(acurve,100)
                     38: apell(acurve,10007)
                     39: apell2(acurve,10007)
                     40: apol=x^3+5*x+1
                     41: apprpadic(apol,1+O(7^8))
                     42: apprpadic(x^3+5*x+1,mod(x*(1+O(7^8)),x^2+x-1))
                     43: 4*arg(3+3*i)
                     44: 3*asin(sqrt(3)/2)
                     45: asinh(0.5)
                     46: assmat(x^5-12*x^3+0.0005)
                     47: 3*atan(sqrt(3))
                     48: atanh(0.5)
                     49: \\ B
                     50: basis(x^3+4*x+5)
                     51: basis2(x^3+4*x+5)
                     52: basistoalg(nf,ba)
                     53: bernreal(12)
                     54: bernvec(6)
                     55: bestappr(pi,10000)
                     56: bezout(123456789,987654321)
                     57: bigomega(12345678987654321)
                     58: mcurve=initell([0,0,0,-17,0])
                     59: mpoints=[[-1,4],[-4,2]]~
                     60: mhbi=bilhell(mcurve,mpoints,[9,24])
                     61: bin(1.1,5)
                     62: binary(65537)
                     63: bittest(10^100,100)
                     64: boundcf(pi,5)
                     65: boundfact(40!+1,100000)
                     66: move(0,0,0);box(0,500,500)
                     67: setrand(1);buchimag(1-10^7,1,1)
                     68: setrand(1);bnf=buchinitfu(x^2-x-57,0.2,0.2)
                     69: buchcertify(bnf)
                     70: buchfu(bnf)
                     71: setrand(1);buchinitforcefu(x^2-x-100000)
                     72: setrand(1);bnf=buchinitfu(x^2-x-57,0.2,0.2)
                     73: setrand(1);buchreal(10^9-3,0,0.5,0.5)
                     74: setrand(1);buchgen(x^4-7,0.2,0.2)
                     75: setrand(1);buchgenfu(x^2-x-100000)
                     76: setrand(1);buchgenforcefu(x^2-x-100000)
                     77: setrand(1);buchgenfu(x^4+24*x^2+585*x+1791,0.1,0.1)
                     78: buchnarrow(bnf)
1.2     ! noro       79: buchray(bnf,[[5,4;0,1],[1,0]])
        !            80: bnr=buchrayinitgen(bnf,[[5,4;0,1],[1,0]])
        !            81: bnr2=buchrayinitgen(bnf,[[25,14;0,1],[1,1]])
1.1       noro       82: bytesize(%)
                     83: \\ C
                     84: ceil(-2.5)
                     85: centerlift(mod(456,555))
                     86: cf(pi)
                     87: cf2([1,3,5,7,9],(exp(1)-1)/(exp(1)+1))
                     88: changevar(x+y,[z,t])
                     89: char([1,2;3,4],z)
                     90: char(mod(x^2+x+1,x^3+5*x+1),z)
                     91: char1([1,2;3,4],z)
                     92: char2(mod(1,8191)*[1,2;3,4],z)
                     93: acurve=chell(acurve,[-1,1,2,3])
                     94: chinese(mod(7,15),mod(13,21))
                     95: apoint=chptell(apoint,[-1,1,2,3])
                     96: isoncurve(acurve,apoint)
                     97: classno(-12391)
                     98: classno(1345)
                     99: classno2(-12391)
                    100: classno2(1345)
                    101: coeff(sin(x),7)
                    102: compimag(qfi(2,1,3),qfi(2,1,3))
                    103: compo(1+o(7^4),3)
                    104: compositum(x^4-4*x+2,x^3-x-1)
                    105: compositum2(x^4-4*x+2,x^3-x-1)
                    106: comprealraw(qfr(5,3,-1,0.),qfr(7,1,-1,0.))
                    107: concat([1,2],[3,4])
1.2     ! noro      108: conductor(bnf,[[25,14;0,1],[1,1]])
1.1       noro      109: conductorofchar(bnr,[2])
                    110: conj(1+i)
                    111: conjvec(mod(x^2+x+1,x^3-x-1))
                    112: content([123,456,789,234])
                    113: convol(sin(x),x*cos(x))
                    114: core(54713282649239)
                    115: core2(54713282649239)
                    116: coredisc(54713282649239)
                    117: coredisc2(54713282649239)
                    118: cos(1)
                    119: cosh(1)
                    120: move(0,200,150)
                    121: cursor(0)
                    122: cvtoi(1.7)
                    123: cyclo(105)
                    124: \\ D
                    125: degree(x^3/(x-1))
                    126: denom(12345/54321)
                    127: deplin(mod(1,7)*[2,-1;1,3])
                    128: deriv((x+y)^5,y)
                    129: ((x+y)^5)'
                    130: det([1,2,3;1,5,6;9,8,7])
                    131: det2([1,2,3;1,5,6;9,8,7])
                    132: detint([1,2,3;4,5,6])
                    133: diagonal([2,4,6])
                    134: dilog(0.5)
                    135: dz=vector(30,k,1);dd=vector(30,k,k==1);dm=dirdiv(dd,dz)
                    136: deu=direuler(p=2,100,1/(1-apell(acurve,p)*x+if(acurve[12]%p,p,0)*x^2))
                    137: anell(acurve,100)==deu
                    138: dirmul(abs(dm),dz)
                    139: dirzetak(initalg(x^3-10*x+8),30)
                    140: disc(x^3+4*x+12)
                    141: discf(x^3+4*x+12)
                    142: discrayabs(bnr,mat(6))
                    143: discrayabs(bnr)
                    144: discrayabscond(bnr2)
                    145: lu=ideallistunitgen(bnf,55);discrayabslist(bnf,lu)
                    146: discrayabslistlong(bnf,20)
                    147: discrayrel(bnr,mat(6))
                    148: discrayrel(bnr)
                    149: discrayrelcond(bnr2)
                    150: divisors(8!)
                    151: divres(345,123)
                    152: divres(x^7-1,x^5+1)
                    153: divsum(8!,x,x)
                    154: \\draw([0,0,0])
                    155: postdraw([0,0,0])
                    156: \\ E
                    157: eigen([1,2,3;4,5,6;7,8,9])
                    158: eint1(2)
                    159: erfc(2)
                    160: eta(q)
                    161: euler
                    162: z=y;y=x;eval(z)
                    163: exp(1)
                    164: extract([1,2,3,4,5,6,7,8,9,10],1000)
                    165: \\ F
                    166: 10!
                    167: fact(10)
                    168: factcantor(x^11+1,7)
                    169: centerlift(lift(factfq(x^3+x^2+x-1,3,t^3+t^2+t-1)))
                    170: factmod(x^11+1,7)
                    171: factor(17!+1)
                    172: p=x^5+3021*x^4-786303*x^3-6826636057*x^2-546603588746*x+3853890514072057
                    173: fa=[11699,6;2392997,2;4987333019653,2]
                    174: factoredbasis(p,fa)
                    175: factoreddiscf(p,fa)
                    176: factoredpolred(p,fa)
                    177: factoredpolred2(p,fa)
                    178: factornf(x^3+x^2-2*x-1,t^3+t^2-2*t-1)
                    179: factorpadic(apol,7,8)
                    180: factorpadic2(apol,7,8)
                    181: factpol(x^15-1,3,1)
                    182: factpol(x^15-1,0,1)
                    183: factpol2(x^15-1,0)
                    184: fibo(100)
                    185: floor(-1/2)
                    186: floor(-2.5)
                    187: for(x=1,5,print(x!))
                    188: fordiv(10,x,print(x))
                    189: forprime(p=1,30,print(p))
                    190: forstep(x=0,pi,pi/12,print(sin(x)))
                    191: forvec(x=[[1,3],[-2,2]],print1([x[1],x[2]]," "));print(" ");
                    192: frac(-2.7)
                    193: \\ G
                    194: galois(x^6-3*x^2-1)
                    195: nf3=initalg(x^6+108);galoisconj(nf3)
                    196: aut=%[2];galoisapply(nf3,aut,mod(x^5,x^6+108))
                    197: gamh(10)
                    198: gamma(10.5)
                    199: gauss(hilbert(10),[1,2,3,4,5,6,7,8,9,0]~)
                    200: gaussmodulo([2,3;5,4],[7,11],[1,4]~)
                    201: gaussmodulo2([2,3;5,4],[7,11],[1,4]~)
                    202: gcd(12345678,87654321)
                    203: getheap()
                    204: getrand()
                    205: getstack()
                    206: \\gettime()isattheend
                    207: globalred(acurve)
                    208: getstack()
                    209: \\ H
                    210: hclassno(2000003)
                    211: hell(acurve,apoint)
                    212: hell2(acurve,apoint)
                    213: hermite(amat=1/hilbert(7))
                    214: hermite2(amat)
                    215: hermitehavas(amat)
                    216: hermitemod(amat,detint(amat))
                    217: hermiteperm(amat)
                    218: hess(hilbert(7))
                    219: hilb(2/3,3/4,5)
                    220: hilbert(5)
                    221: hilbp(mod(5,7),mod(6,7))
                    222: hvector(10,x,1/x)
                    223: hyperu(1,1,1)
                    224: \\ I
                    225: i^2
                    226: nf1=initalgred(nfpol)
                    227: initalgred2(nfpol)
                    228: vp=primedec(nf,3)[1]
                    229: idx=idealmul(nf,idmat(5),vp)
                    230: idealinv(nf,idx)
                    231: idy=ideallllred(nf,idx,[1,5,6])
                    232: idealadd(nf,idx,idy)
                    233: idealaddone(nf,idx,idy)
                    234: idealaddmultone(nf,[idy,idx])
                    235: idealappr(nf,idy)
                    236: idealapprfact(nf,idealfactor(nf,idy))
                    237: idealcoprime(nf,idx,idx)
                    238: idz=idealintersect(nf,idx,idy)
                    239: idealfactor(nf,idz)
                    240: ideallist(bnf,20)
                    241: idx2=idealmul(nf,idx,idx)
                    242: idt=idealmulred(nf,idx,idx)
                    243: idealdiv(nf,idy,idt)
                    244: idealdivexact(nf,idx2,idx)
                    245: idealhermite(nf,vp)
                    246: idealhermite2(nf,vp[2],3)
                    247: idealnorm(nf,idt)
                    248: idp=idealpow(nf,idx,7)
                    249: idealpowred(nf,idx,7)
                    250: idealtwoelt(nf,idy)
                    251: idealtwoelt2(nf,idy,10)
                    252: idealval(nf,idp,vp)
                    253: idmat(5)
                    254: if(3<2,print("bof"),print("ok"));
                    255: imag(2+3*i)
                    256: image([1,3,5;2,4,6;3,5,7])
                    257: image(pi*[1,3,5;2,4,6;3,5,7])
                    258: incgam(2,1)
                    259: incgam1(2,1)
                    260: incgam2(2,1)
                    261: incgam3(2,1)
                    262: incgam4(4,1,6)
                    263: indexrank([1,1,1;1,1,1;1,1,2])
                    264: indsort([8,7,6,5])
                    265: initell([0,0,0,-1,0])
                    266: initrect(1,700,700)
                    267: nfz=initzeta(x^2-2);
                    268: integ(sin(x),x)
                    269: integ((-x^2-2*a*x+8*a)/(x^4-14*x^3+(2*a+49)*x^2-14*a*x+a^2),x)
                    270: intersect([1,2;3,4;5,6],[2,3;7,8;8,9])
                    271: \precision=19
                    272: intgen(x=0,pi,sin(x))
                    273: sqr(2*intgen(x=0,4,exp(-x^2)))
                    274: 4*intinf(x=1,10^20,1/(1+x^2))
                    275: intnum(x=-0.5,0.5,1/sqrt(1-x^2))
                    276: 2*intopen(x=0,100,sin(x)/x)
                    277: \precision=38
                    278: inverseimage([1,1;2,3;5,7],[2,2,6]~)
                    279: isdiagonal([1,0,0;0,5,0;0,0,0])
                    280: isfund(12345)
1.2     ! noro      281: isideal(bnf[7],[5,2;0,1])
1.1       noro      282: isincl(x^2+1,x^4+1)
                    283: isinclfast(initalg(x^2+1),initalg(x^4+1))
                    284: isirreducible(x^5+3*x^3+5*x^2+15)
                    285: isisom(x^3+x^2-2*x-1,x^3+x^2-2*x-1)
                    286: isisomfast(initalg(x^3-2),initalg(x^3-6*x^2-6*x-30))
                    287: isprime(12345678901234567)
1.2     ! noro      288: isprincipal(bnf,[5,2;0,1])
        !           289: isprincipalgen(bnf,[5,2;0,1])
1.1       noro      290: isprincipalraygen(bnr,primedec(bnf,7)[1])
                    291: ispsp(73!+1)
                    292: isqrt(10!^2+1)
                    293: isset([-3,5,7,7])
                    294: issqfree(123456789876543219)
                    295: issquare(12345678987654321)
                    296: isunit(bnf,mod(3405*x-27466,x^2-x-57))
                    297: \\ J
                    298: jacobi(hilbert(6))
                    299: jbesselh(1,1)
                    300: jell(i)
                    301: \\ K
                    302: kbessel(1+i,1)
                    303: kbessel2(1+i,1)
                    304: x
                    305: y
                    306: ker(matrix(4,4,x,y,x/y))
                    307: ker(matrix(4,4,x,y,sin(x+y)))
                    308: keri(matrix(4,4,x,y,x+y))
                    309: kerint(matrix(4,4,x,y,x*y))
                    310: kerint1(matrix(4,4,x,y,x*y))
                    311: kerint2(matrix(4,6,x,y,2520/(x+y)))
                    312: f(u)=u+1;
                    313: print(f(5));kill(f);
                    314: f=12
                    315: killrect(1)
                    316: kro(5,7)
                    317: kro(3,18)
                    318: \\ L
                    319: laplace(x*exp(x*y)/(exp(x)-1))
                    320: lcm(15,-21)
                    321: length(divisors(1000))
                    322: legendre(10)
                    323: lex([1,3],[1,3,5])
                    324: lexsort([[1,5],[2,4],[1,5,1],[1,4,2]])
                    325: lift(chinese(mod(7,15),mod(4,21)))
                    326: lindep([(1-3*sqrt(2))/(3-2*sqrt(3)),1,sqrt(2),sqrt(3),sqrt(6)])
                    327: lindep2([(1-3*sqrt(2))/(3-2*sqrt(3)),1,sqrt(2),sqrt(3),sqrt(6)],14)
                    328: move(0,0,900);line(0,900,0)
                    329: lines(0,vector(5,k,50*k),vector(5,k,10*k*k))
                    330: m=1/hilbert(7)
                    331: mp=concat(m,idmat(7))
                    332: lll(m)
                    333: lll1(m)
                    334: lllgram(m)
                    335: lllgram1(m)
                    336: lllgramint(m)
                    337: lllgramkerim(mp~*mp)
                    338: lllint(m)
                    339: lllintpartial(m)
                    340: lllkerim(mp)
                    341: lllrat(m)
                    342: \precision=96
                    343: ln(2)
                    344: lngamma(10^50*i)
                    345: \precision=2000
                    346: log(2)
                    347: logagm(2)
                    348: \precision=19
                    349: bcurve=initell([0,0,0,-3,0])
                    350: localred(bcurve,2)
                    351: ccurve=initell([0,0,-1,-1,0])
                    352: l=lseriesell(ccurve,2,-37,1)
                    353: lseriesell(ccurve,2,-37,1.2)-l
                    354: \\ M
                    355: sbnf=smallbuchinit(x^3-x^2-14*x-1)
                    356: makebigbnf(sbnf)
                    357: concat(mat(vector(4,x,x)~),vector(4,x,10+x)~)
                    358: matextract(matrix(15,15,x,y,x+y),vector(5,x,3*x),vector(3,y,3*y))
                    359: ma=mathell(mcurve,mpoints)
                    360: gauss(ma,mhbi)
                    361: (1.*hilbert(7))^(-1)
                    362: matsize([1,2;3,4;5,6])
                    363: matrix(5,5,x,y,gcd(x,y))
                    364: matrixqz([1,3;3,5;5,7],0)
                    365: matrixqz2([1/3,1/4,1/6;1/2,1/4,-1/4;1/3,1,0])
                    366: matrixqz3([1,3;3,5;5,7])
                    367: max(2,3)
                    368: min(2,3)
                    369: minim([2,1;1,2],4,6)
                    370: mod(-12,7)
                    371: modp(-12,7)
                    372: mod(10873,49649)^-1
                    373: modreverse(mod(x^2+1,x^3-x-1))
                    374: move(0,243,583);cursor(0)
                    375: mu(3*5*7*11*13)
                    376: \\ N
                    377: newtonpoly(x^4+3*x^3+27*x^2+9*x+81,3)
                    378: nextprime(100000000000000000000000)
                    379: setrand(1);a=matrix(3,5,j,k,vvector(5,l,random()\10^8))
                    380: aid=[idx,idy,idz,idmat(5),idx]
                    381: bb=algtobasis(nf,mod(x^3+x,nfpol))
                    382: da=nfdetint(nf,[a,aid])
                    383: nfdiv(nf,ba,bb)
                    384: nfdiveuc(nf,ba,bb)
                    385: nfdivres(nf,ba,bb)
                    386: nfhermite(nf,[a,aid])
                    387: nfhermitemod(nf,[a,aid],da)
                    388: nfmod(nf,ba,bb)
                    389: nfmul(nf,ba,bb)
                    390: nfpow(nf,bb,5)
                    391: nfreduce(nf,ba,idx)
                    392: setrand(1);as=matrix(3,3,j,k,vvector(5,l,random()\10^8))
                    393: vaid=[idx,idy,idmat(5)]
                    394: haid=[idmat(5),idmat(5),idmat(5)]
                    395: nfsmith(nf,[as,haid,vaid])
                    396: nfval(nf,ba,vp)
                    397: norm(1+i)
                    398: norm(mod(x+5,x^3+x+1))
                    399: norml2(vector(10,x,x))
                    400: nucomp(qfi(2,1,9),qfi(4,3,5),3)
                    401: form=qfi(2,1,9);nucomp(form,form,3)
                    402: numdiv(2^99*3^49)
                    403: numer((x+1)/(x-1))
                    404: nupow(form,111)
                    405: \\ O
                    406: 1/(1+x)+o(x^20)
                    407: omega(100!)
                    408: ordell(acurve,1)
                    409: order(mod(33,2^16+1))
                    410: tcurve=initell([1,0,1,-19,26]);
                    411: orderell(tcurve,[1,2])
                    412: ordred(x^3-12*x+45*x-1)
                    413: \\ P
                    414: padicprec(padicno,127)
                    415: pascal(8)
                    416: perf([2,0,1;0,2,1;1,1,2])
                    417: permutation(7,1035)
                    418: permutation2num([4,7,1,6,3,5,2])
                    419: pf(-44,3)
                    420: phi(257^2)
                    421: pi
                    422: plot(x=-5,5,sin(x))
                    423: \\ploth(x=-5,5,sin(x))
                    424: \\ploth2(t=0,2*pi,[sin(5*t),sin(7*t)])
                    425: \\plothraw(vector(100,k,k),vector(100,k,k*k/100))
                    426: pnqn([2,6,10,14,18,22,26])
                    427: pnqn([1,1,1,1,1,1,1,1;1,1,1,1,1,1,1,1])
                    428: point(0,225,334)
                    429: points(0,vector(10,k,10*k),vector(10,k,5*k*k))
                    430: pointell(acurve,zell(acurve,apoint))
                    431: polint([0,2,3],[0,4,9],5)
                    432: polred(x^5-2*x^4-4*x^3-96*x^2-352*x-568)
                    433: polred2(x^4-28*x^3-458*x^2+9156*x-25321)
                    434: polredabs(x^5-2*x^4-4*x^3-96*x^2-352*x-568)
                    435: polredabs2(x^5-2*x^4-4*x^3-96*x^2-352*x-568)
                    436: polsym(x^17-1,17)
                    437: polvar(name^4-other)
                    438: poly(sin(x),x)
                    439: polylog(5,0.5)
                    440: polylog(-4,t)
                    441: polylogd(5,0.5)
                    442: polylogdold(5,0.5)
                    443: polylogp(5,0.5)
                    444: poly([1,2,3,4,5],x)
                    445: polyrev([1,2,3,4,5],x)
                    446: polzag(6,3)
                    447: \\draw([0,20,20])
                    448: postdraw([0,20,20])
                    449: postploth(x=-5,5,sin(x))
                    450: postploth2(t=0,2*pi,[sin(5*t),sin(7*t)])
                    451: postplothraw(vector(100,k,k),vector(100,k,k*k/100))
                    452: powell(acurve,apoint,10)
                    453: cmcurve=initell([0,-3/4,0,-2,-1])
                    454: powell(cmcurve,[x,y],quadgen(-7))
                    455: powrealraw(qfr(5,3,-1,0.),3)
                    456: pprint((x-12*y)/(y+13*x));
                    457: pprint([1,2;3,4])
                    458: pprint1(x+y);pprint(x+y);
                    459: \precision=96
                    460: pi
                    461: prec(pi,20)
                    462: precision(cmcurve)
                    463: \precision=38
                    464: prime(100)
                    465: primedec(nf,2)
                    466: primedec(nf,3)
                    467: primedec(nf,11)
                    468: primes(100)
                    469: forprime(p=2,100,print(p," ",lift(primroot(p))))
                    470: principalideal(nf,mod(x^3+5,nfpol))
                    471: principalidele(nf,mod(x^3+5,nfpol))
                    472: print((x-12*y)/(y+13*x));
                    473: print([1,2;3,4])
                    474: print1(x+y);print1(" equals ");print(x+y);
                    475: prod(1,k=1,10,1+1/k!)
                    476: prod(1.,k=1,10,1+1/k!)
                    477: pi^2/6*prodeuler(p=2,10000,1-p^-2)
                    478: prodinf(n=0,(1+2^-n)/(1+2^(-n+1)))
                    479: prodinf1(n=0,-2^-n/(1+2^(-n+1)))
                    480: psi(1)
                    481: \\ Q
                    482: quaddisc(-252)
                    483: quadgen(-11)
                    484: quadpoly(-11)
                    485: \\ R
                    486: rank(matrix(5,5,x,y,x+y))
1.2     ! noro      487: rayclassno(bnf,[[5,4;0,1],[1,0]])
1.1       noro      488: rayclassnolist(bnf,lu)
                    489: move(0,50,50);rbox(0,50,50)
                    490: print1("give a value for s? ");s=read();print(1/s)
                    491: 37.
                    492: real(5-7*i)
                    493: recip(3*x^7-5*x^3+6*x-9)
                    494: redimag(qfi(3,10,12))
                    495: redreal(qfr(3,10,-20,1.5))
                    496: redrealnod(qfr(3,10,-20,1.5),18)
                    497: reduceddisc(x^3+4*x+12)
                    498: regula(17)
                    499: kill(y);print(x+y);reorder([x,y]);print(x+y);
                    500: resultant(x^3-1,x^3+1)
                    501: resultant2(x^3-1.,x^3+1.)
                    502: reverse(tan(x))
                    503: rhoreal(qfr(3,10,-20,1.5))
                    504: rhorealnod(qfr(3,10,-20,1.5),18)
                    505: rline(0,200,150)
                    506: cursor(0)
                    507: rmove(0,5,5);cursor(0)
                    508: rndtoi(prod(1,k=1,17,x-exp(2*i*pi*k/17)))
                    509: qpol=y^3-y-1;setrand(1);bnf2=buchinit(qpol);nf2=bnf2[7];
                    510: un=mod(1,qpol);w=mod(y,qpol);p=un*(x^5-5*x+w)
                    511: aa=rnfpseudobasis(nf2,p)
                    512: rnfbasis(bnf2,aa)
                    513: rnfdiscf(nf2,p)
                    514: rnfequation(nf2,p)
                    515: rnfequation2(nf2,p)
                    516: rnfhermitebasis(bnf2,aa)
                    517: rnfisfree(bnf2,aa)
                    518: rnfsteinitz(nf2,aa)
                    519: rootmod(x^16-1,41)
                    520: rootpadic(x^4+1,41,6)
                    521: roots(x^5-5*x^2-5*x-5)
                    522: rootsold(x^4-1000000000000000000000)
                    523: round(prod(1,k=1,17,x-exp(2*i*pi*k/17)))
                    524: rounderror(prod(1,k=1,17,x-exp(2*i*pi*k/17)))
                    525: rpoint(0,20,20)
                    526: \\ S
                    527: initrect(3,600,600);scale(3,-7,7,-2,2);cursor(3)
                    528: q*series(anell(acurve,100),q)
                    529: aset=set([5,-2,7,3,5,1])
                    530: bset=set([7,5,-5,7,2])
                    531: setintersect(aset,bset)
                    532: setminus(aset,bset)
                    533: setprecision(28)
                    534: setrand(10)
                    535: setsearch(aset,3)
                    536: setsearch(bset,3)
                    537: setserieslength(12)
                    538: setunion(aset,bset)
                    539: arat=(x^3+x+1)/x^3;settype(arat,14)
                    540: shift(1,50)
                    541: shift([3,4,-11,-12],-2)
                    542: shiftmul([3,4,-11,-12],-2)
                    543: sigma(100)
                    544: sigmak(2,100)
                    545: sigmak(-3,100)
                    546: sign(-1)
                    547: sign(0)
                    548: sign(0.)
                    549: signat(hilbert(5)-0.11*idmat(5))
                    550: signunit(bnf)
                    551: simplefactmod(x^11+1,7)
                    552: simplify(((x+i+1)^2-x^2-2*x*(i+1))^2)
                    553: sin(pi/6)
                    554: sinh(1)
                    555: size([1.3*10^5,2*i*pi*exp(4*pi)])
                    556: smallbasis(x^3+4*x+12)
                    557: smalldiscf(x^3+4*x+12)
                    558: smallfact(100!+1)
                    559: smallinitell([0,0,0,-17,0])
                    560: smallpolred(x^4+576)
                    561: smallpolred2(x^4+576)
                    562: smith(matrix(5,5,j,k,random()))
                    563: smith(1/hilbert(6))
                    564: smithpol(x*idmat(5)-matrix(5,5,j,k,1))
                    565: solve(x=1,4,sin(x))
                    566: sort(vector(17,x,5*x%17))
                    567: sqr(1+o(2))
                    568: sqred(hilbert(5))
                    569: sqrt(13+o(127^12))
                    570: srgcd(x^10-1,x^15-1)
                    571: move(0,100,100);string(0,pi)
                    572: move(0,200,200);string(0,"(0,0)")
                    573: \\draw([0,10,10])
                    574: postdraw([0,10,10])
                    575: apol=0.3+legendre(10)
                    576: sturm(apol)
                    577: sturmpart(apol,0.91,1)
                    578: subcyclo(31,5)
                    579: subell(initell([0,0,0,-17,0]),[-1,4],[-4,2])
                    580: subst(sin(x),x,y)
                    581: subst(sin(x),x,x+x^2)
                    582: sum(0,k=1,10,2^-k)
                    583: sum(0.,k=1,10,2^-k)
                    584: sylvestermatrix(a2*x^2+a1*x+a0,b1*x+b0)
                    585: \precision=38
                    586: 4*sumalt(n=0,(-1)^n/(2*n+1))
                    587: 4*sumalt2(n=0,(-1)^n/(2*n+1))
                    588: suminf(n=1,2.^-n)
                    589: 6/pi^2*sumpos(n=1,n^-2)
                    590: supplement([1,3;2,4;3,6])
                    591: \\ T
                    592: sqr(tan(pi/3))
                    593: tanh(1)
                    594: taniyama(bcurve)
                    595: taylor(y/(x-y),y)
                    596: tchebi(10)
                    597: teich(7+o(127^12))
                    598: texprint((x+y)^3/(x-y)^2)
                    599: theta(0.5,3)
                    600: thetanullk(0.5,7)
                    601: torsell(tcurve)
                    602: trace(1+i)
                    603: trace(mod(x+5,x^3+x+1))
                    604: trans(vector(2,x,x))
                    605: %*%~
                    606: trunc(-2.7)
                    607: trunc(sin(x^2))
                    608: tschirnhaus(x^5-x-1)
                    609: type(mod(x,x^2+1))
                    610: \\ U
                    611: unit(17)
                    612: n=33;until(n==1,print1(n," ");if(n%2,n=3*n+1,n=n/2));print(1)
                    613: \\ V
                    614: valuation(6^10000-1,5)
                    615: vec(sin(x))
                    616: vecmax([-3,7,-2,11])
                    617: vecmin([-3,7,-2,11])
                    618: vecsort([[1,8,5],[2,5,8],[3,6,-6],[4,8,6]],2)
                    619: vecsort([[1,8,5],[2,5,8],[3,6,-6],[4,8,6]],[2,1])
                    620: \\ W
                    621: weipell(acurve)
                    622: wf(i)
                    623: wf2(i)
                    624: m=5;while(m<20,print1(m," ");m=m+1);print()
                    625: \\ Z
                    626: zell(acurve,apoint)
                    627: zeta(3)
                    628: zeta(0.5+14.1347251*i)
                    629: zetak(nfz,-3)
                    630: zetak(nfz,1.5+3*i)
                    631: zidealstar(nf2,54)
                    632: bid=zidealstarinit(nf2,54)
                    633: zideallog(nf2,w,bid)
                    634: znstar(3120)
                    635: getstack()
                    636: getheap()
                    637: print("Total time spent: ",gettime());
                    638: \q

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>