cond-mat0701674/POLYMER
1: print(`This is the package POLYMER`):
2: print(`written by Arvind Ayyer and Doron Zeilberger`):
3: print(`It is written for the analysis of directed lattice walks`):
4: print(`in two dimensions with arbitrary set of steps`):
5: print(`It uses some functions from GuessHolo2`):
6: print(`written by D. Zeilberger`):
7: print(`To see the list of procedures, type Help();`):
8: print(`For help on a specific procedure, type Help(procedure_name);`):
9: 
10: 
11: Help := proc()
12: 
13: if args=NULL then
14: 
15: 
16: print(`Contains the following procedures`):
17: print(`Number of walks: polymer, WEpolymer, polymerBE, WEpolymerBE`):
18: print(`Recurrences: stepsrec, WEstepsrec,`):
19: print(`Generating functions: rigorgf, rigorgfWE, RGF2D, RGF2DWE`):
20: print(`Plotting commands: plotFE, plotFEWE, ForceWE, plotinfFEWE`):
21: print(`NOTE: The plots are best viewed in the Graphical Version`):
22: 
23: fi:
24: 
25: if nops([args])=1 and op(1,[args])=`polymer` then
26: print(`polymer(Steps,a,w) uses steps given in Steps `):
27: print(`to calculate the number of ways of walking upto a from the origin`):
28: print(`where the walk is confined between the lines x-y=0 and x-y=w.`):
29: print(`For example, try polymer({[0,1],[1,0]},[2,2],3);`):
30: fi:
31: 
32: if nops([args])=1 and op(1,[args])=`polymerBE` then
33: print(`polymer(Steps,a,b,w) uses steps given in Steps `):
34: print(`to calculate the number of ways of walking from a to b`):
35: print(`where the walk is confined between the lines x-y=0 and x-y=w.`):
36: print(`For example, try polymerBE({[0,1],[1,0]},[1,1],[2,2],3);`):
37: fi:
38: 
39: if nops([args])=1 and op(1,[args])=`WEpolymer` then
40: print(`WEpolymer(Steps,a,w,t,s) uses steps given in Steps `):
41: print(`to calculate the enumerated walk from 0 to a`):
42: print(`where the walk is confined between the lines x-y=0 and x-y=w`):
43: print(`and t,s mark the number of times they are hit respectively.`):
44: print(`For example, try WEpolymer({[0,1],[1,0]},[2,2],2,t,s);`):
45: fi:
46: 
47: if nops([args])=1 and op(1,[args])=`WEpolymerBE` then
48: print(`WEpolymer(Steps,a,b,w,t,s) uses steps given in Steps `):
49: print(`to calculate the enumerated walk from a to b`):
50: print(`where the walk is confined between the lines x-y=0 and x-y=w`):
51: print(`and t,s mark the number of times they are hit respectively.`):
52: print(`For example, try WEpolymerBE({[0,1],[1,0]},[1,1],[2,2],2,t,s);`):
53: fi:
54: 
55: if nops([args])=1 and op(1,[args])=`stepsrec` then
56: print(`stepsrec(Steps,METADEGREE,METAORDER,N,w,W) finds an operator, if it exists,`):
57: print(`of order METAORDER and degree METADEGREE which annihilates denominators`):
58: print(`of subsequent generating functions as a function of N of sufficiently many widths.`):
59: print(`For example, try stepsrec({[1,0],[0,1]},0,2,N,w,W);`):
60: fi:
61: 
62: 
63: if nops([args])=1 and op(1,[args])=`WEstepsrec` then
64: print(`WEstepsrec(Steps,METADEGREE,METAORDER,N,w,W) finds an operator, if it exists,`):
65: print(`of order METAORDER and degree METADEGREE which annihilates denominators`):
66: print(`of subsequent weight enumerating generating functions as a function of N,t,s of sufficiently many widths.`):
67: print(`For example, try WEstepsrec({[1,0],[0,1]},0,2,N,w,W,t,s);`):
68: fi:
69: 
70: 
71: if nops([args])=1 and op(1,[args])=`rigorgf` then
72: print(`rigorgf(Steps,w,z) calculates the generating function exactly`):
73: print(`of walks with Steps and width w in the variable z.`):
74: print(`Try, for example, rigorgf({[0,1],[1,0]},2,z);`):
75: fi:
76: 
77: if nops([args])=1 and op(1,[args])=`rigorgfWE` then
78: print(`rigorgfWE(Steps,w,z,t,s) calculates the generating function exactly`):
79: print(`of walks with Steps and width w in the variable z`):
80: print(`where t,s mark the number of times the walk hits`):
81: print(`the lines x-y=0 and x-y=w respectively.`):
82: print(`Try, for example, rigorgfWE({[0,1],[1,0]},2,z,t,s);`):
83: fi:
84: 
85: if nops([args])=1 and op(1,[args])=`RGF2D` then
86: print(`RGF2D(Steps,z,F) rigorously finds the polynomial equation`):
87: print(`satisfied by the generating function F(z)`):
88: print(`for a walk with arbitrary sequence of steps with infinite width.`):
89: print(`Try, for example, RGF2D({[0,1],[1,0]},z,F);`):
90: fi:
91: 
92: if nops([args])=1 and op(1,[args])=`RGF2DWE` then
93: print(`RGF2DWE(Steps,z,F,t) rigorously finds the polynomial equation`):
94: print(`satisfied by the generating function F(z;t)`):
95: print(`for a walk with arbitrary sequence of steps with infinite width`):
96: print(`where the parameter t marks the number of times the walk`):
97: print(`hits the line x-y=0.`):
98: print(`Try, for example, RGF2DWE({[0,1],[1,0]},z,F,t);`):
99: fi:
100: 
101: if nops([args])=1 and op(1,[args])=`rgfprove` then
102: print(`rgfprove(Steps,OPE,W,N) when given OPE(W,N), the ope satisfied by the denominators`):
103: print(`of the generating functions as a function of N and the shift operator W`):
104: print(`verifies whether the implied relation for the GF is true.`):
105: print(`Try, for example, rgfprove({[0,1],[1,0]},N-W+W^2,W,N)`):
106: fi:
107: 
108: if nops([args])=1 and op(1,[args])=`plotFE` then
109: print(`plotFE(Steps,winit,wfin) plots the numerical value of the free energy`):
110: print(`when given the set of steps and the initial and final integer widths.`):
111: print(`Try, for example, plotFE({[0,1],[1,0]},1,10); `):
112: fi:
113: 
114: if nops([args])=1 and op(1,[args])=`plotFEWE` then
115: print(`plotFEWE(Steps,w,tmin,tmax,smin,smax) plots the free energy for a`):
116: print(`given set of steps and width. The ranges of the weight enumerating`):
117: print(`parameters t,s are to be specified.`):
118: print(`Try, for example, plotFEWE({[0,1],[1,0]},3,1,4,1,4); `):
119: fi:
120: 
121: if nops([args])=1 and op(1,[args])=`ForceWE` then
122: print(`ForceWE(Steps,w,tmin,tmax,smin,smax) plot the force for a`):
123: print(`given set of steps and width. The ranges of the weight enumerating`):
124: print(`parameters t,s are to be specified.`):
125: print(`Try, for example, ForceWE({[0,1],[1,0]},3,1,4,1,4); `):
126: fi:
127: 
128: if nops([args])=1 and op(1,[args])=`plotinfFEWE` then
129: print(`plotinfFEWE(Steps,tmin,tmax) finds the Free Energy for the`):
130: print(`set Steps with the weight enumerating parameter varying from `):
131: print(`integers tmin to tmax.`):
132: print(`Try, for example, plotinfFEWE({[0,1],[1,0]},1,5);`):
133: fi:
134: 
135: end:
136: 
137: with(combinat):
138: with(gfun):
139: with(SolveTools):
140: with(plots):
141: 
142: 
143: 
144: #polymer(Steps,a,w) uses steps given in Steps to calculate the number of ways of walking upto a where the walk is confined between the lines x-y=0 and x-y=w
145: polymer := proc(Steps, a, w) local i,j,k,Prev:
146: option remember:
147: 
148: k := nops(a):
149: 
150: if k <> nops(Steps[1]) then
151: 	return FAIL:
152: fi:
153: 
154: if a=[0$k] then
155: 	return 1:
156: fi:
157: 
158: #HAVE TO REPLACE THIS WITH THE PROPER CONDITION 
159: #if min(op(a))<0 then
160: #	return 0:
161: #fi:
162: 
163: #THIS SEEMS RIGHT
164: if sum(a[i],i=1..nops(a)) < 0 then
165: 	return 0:
166: fi:
167: 
168: if min(seq(a[i]-a[i+1],i=1..nops(a)-1))<0 then
169: 	return 0:
170: fi:
171: 
172: if max(seq(a[i]-a[i+1],i=1..nops(a)-1))>w then
173: 	return 0:
174: fi:
175: 
176: Prev:={seq([seq(a[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
177: return add(polymer(Steps,Prev[i],w),i=1..nops(Prev)):
178: 
179: end:
180: 
181: #polymerBE(Steps,a,b,w) uses steps given in Steps to calculate the number of ways of walking from a to b where the walk is confined between the lines x-y=0 and x-y=w
182: polymerBE := proc(Steps, a, b, w) local i,j,k,ba,Prev:
183: option remember:
184: 
185: k := nops(a):
186: ba := b-a:
187: 
188: if k <> nops(Steps[1]) then
189: 	return FAIL:
190: fi:
191: 
192: #HAVE TO REPLACE THIS WITH THE PROPER CONDITION 
193: #if min(op(ba))<0 then
194: #	return 0:
195: #fi:
196: 
197: #THIS SEEMS RIGHT
198: if sum(ba[i],i=1..nops(ba)) < 0 then
199: 	return 0:
200: fi:
201: 
202: if min(seq(a[i]-a[i+1],i=1..nops(a)-1))<0 then
203: 	return 0:
204: fi:
205: 
206: if max(seq(a[i]-a[i+1],i=1..nops(a)-1))>w then
207: 	return 0:
208: fi:
209: 
210: if min(seq(b[i]-b[i+1],i=1..nops(b)-1))<0 then
211: 	return 0:
212: fi:
213: 
214: if max(seq(b[i]-b[i+1],i=1..nops(b)-1))>w then
215: 	return 0:
216: fi:
217: 
218: if ba=[0$k] then
219: 	return 1:
220: fi:
221: 
222: Prev:={seq([seq(b[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
223: return add(polymerBE(Steps,a,Prev[i],w),i=1..nops(Prev)):
224: 
225: end:
226: 
227: 
228: #WEpolymerBE(Steps,a,b,w,t,s) uses steps given in Steps to calculate the number of ways of walking from a to b where the walk is confined between the lines x-y=0 and x-y=w
229: WEpolymerBE := proc(Steps, a, b, w,t,s) local i,j,k,ba,Prev:
230: option remember:
231: 
232: k := nops(a):
233: ba := b-a:
234: 
235: if k <> nops(Steps[1]) then
236: 	return FAIL:
237: fi:
238: 
239: if min(op(ba))<0 then
240: 	return 0:
241: fi:
242: 
243: if min(seq(a[i]-a[i+1],i=1..nops(a)-1))<0 then
244: 	return 0:
245: fi:
246: 
247: if max(seq(a[i]-a[i+1],i=1..nops(a)-1))>w then
248: 	return 0:
249: fi:
250: 
251: if min(seq(b[i]-b[i+1],i=1..nops(b)-1))<0 then
252: 	return 0:
253: fi:
254: 
255: if max(seq(b[i]-b[i+1],i=1..nops(b)-1))>w then
256: 	return 0:
257: fi:
258: 
259: if ba=[0$k] then
260: 	return 1:
261: fi:
262: 
263: 
264: if min(seq(b[i]-b[i+1],i=1..nops(b)-1))=0 then
265: 	Prev:={seq([seq(b[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
266: 	return simplify(t*add(WEpolymerBE(Steps,a,Prev[i],w,t,s),i=1..nops(Prev))):
267: fi:
268: 
269: if max(seq(b[i]-b[i+1],i=1..nops(b)-1))=w then
270: 	Prev:={seq([seq(b[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
271: 	return simplify(s*add(WEpolymerBE(Steps,a,Prev[i],w,t,s),i=1..nops(Prev))):
272: fi:
273: 
274: 
275: Prev:={seq([seq(b[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
276: return add(WEpolymerBE(Steps,a,Prev[i],w,t,s),i=1..nops(Prev)):
277: 
278: end:
279: 
280: 
281: 
282: 
283: #WEpolymer(Steps,a,w,t,s) uses steps given in Steps to calculate the weight enumerator of the number of ways of walking upto a where the walk is confined between the lines x-y=0 and x-y=w (t marks the 0-hyperplane and s marks the w-hyperplane)
284: WEpolymer := proc(Steps, a, w,t,s) local i,j,k,Prev:
285: option remember:
286: 
287: k := nops(a):
288: 
289: if k <> nops(Steps[1]) then
290: 	return FAIL:
291: fi:
292: 
293: if a=[0$k] then
294: 	return 1:
295: fi:
296: 
297: if min(op(a))<0 then
298: 	return 0:
299: fi:
300: 
301: if min(seq(a[i]-a[i+1],i=1..nops(a)-1))<0 then
302: 	return 0:
303: fi:
304: 
305: if max(seq(a[i]-a[i+1],i=1..nops(a)-1))>w then
306: 	return 0:
307: fi:
308: 
309: if min(seq(a[i]-a[i+1],i=1..nops(a)-1))=0 then
310: 	Prev:={seq([seq(a[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
311: 	return simplify(t*add(WEpolymer(Steps,Prev[i],w,t,s),i=1..nops(Prev))):
312: fi:
313: 
314: if max(seq(a[i]-a[i+1],i=1..nops(a)-1))=w then
315: 	Prev:={seq([seq(a[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
316: 	return simplify(s*add(WEpolymer(Steps,Prev[i],w,t,s),i=1..nops(Prev))):
317: fi:
318: 
319: Prev:={seq([seq(a[j]-Steps[i][j],j=1..k)],i=1..nops(Steps))}:
320: return add(WEpolymer(Steps,Prev[i],w,t,s),i=1..nops(Prev)):
321: 
322: end:
323: 
324: 
325: 
326: 
327: #stepsrec(Steps,METADEGREE,METAORDER,N,w,W) finds an operator, if it exists, of order METAORDER and degree METADEGREE which annihilates denominators of subsequent generating functions (functions of N) of sufficiently many widths
328: stepsrec := proc(Steps,METADEGREE,METAORDER,N,w,W) local i,ans,sol,width,make_sol:
329: 
330: width := (1+METADEGREE)*(1+METAORDER)+5+METAORDER:
331: 
332: make_sol := proc(i) local res;
333:     res := denom(rigorgf(Steps,i,N));
334:     `if`(coeff(res, N, 0)<0, -1, 1)*res;
335: end;
336: 
337: sol := Vector(width, make_sol);
338: 
339: ans := findrec(sol,METADEGREE,METAORDER,w,W):
340: 
341: #print(sol):
342: RETURN(`Meta-recursion yields`,ans):
343: 
344: 
345: end:
346: 
347: 
348: #WEstepsrec(Steps,METADEGREE,METAORDER,N,w,W,t,s) finds an operator, if it exists, of order METAORDER and degree METADEGREE which annihilates denominators of subsequent weight enumerators (functions of N,t,s) of sufficiently many widths
349: WEstepsrec := proc(Steps,METADEGREE,METAORDER,N,w,W,t,s) local i,ans,sol,width:
350: 
351: width := (1+METADEGREE)*(1+METAORDER)+5+METAORDER:
352: 
353: sol := [seq(denom(rigorgfWE(Steps,i,N,t,s)),i=1..width)]:
354: 
355: for i from 1 to nops(sol) do
356: 	if coeff(sol[i],N,0) < 0 then
357: 		sol[i] := -sol[i]:
358: 	fi:
359: od:
360: 
361: sol := Vector(sol):
362: 
363: ans := findrec(sol,METADEGREE,METAORDER,w,W):
364: 
365: #print(sol):
366: RETURN(`Meta-recursion yields`,ans):
367: 
368: 
369: 
370: end:
371: 
372: 
373: #algeqtorec(eqn,F,z,N,n) returns the recurrence operator as a function of N and n given the algebraic equation eqn(z,F(z))=0
374: algeqtorec := proc(eqn,F,z,N,n) local i,j,deqns,deqn,reqns,reqn,ord,ope,P:
375: 
376: deqns := algeqtodiffeq(eqn,F(z)):
377: 
378: if type(deqns,set) then
379: 	for i from 1 to nops(deqns) do
380: 		if type(deqns[i],`+`) then
381: 			deqn := deqns[i]:
382: 		fi:
383: 	od:
384: else
385: 	deqn := deqns:
386: fi:
387: 
388: 
389: reqns := diffeqtorec(deqn,F(z),P(n)):
390: 
391: if type(reqns,set) then
392: 	for i from 1 to nops(reqns) do
393: 		if type(reqns[i],`+`) then
394: 			reqn := reqns[i]:
395: 		fi:
396: 	od:
397: else
398: 	reqn := reqns:
399: fi:
400: 
401: 
402: #ord := nops(reqn)-1:
403: ord := max(seq(op(1,op(2,op(i,reqn))),i=1..nops(reqn)))-n:
404: 
405: 
406: 
407: 
408: ope := subs({seq(P(n+i)=N^i,i=0..ord)},reqn):
409: 
410: return ope:
411: 
412: 
413: end:
414: 
415: 
416: #Asy(eq,F,z) given the algebraic equation satisfied by the generating function, returns the free energy
417: Asy := proc(eqn,F,z) local i,deqn,deq,deq2,poly,sols:
418: 
419: deqn := algeqtodiffeq(eqn,F(z)):
420: 
421: 
422: if type(deqn,set) then
423: 	for i from 1 to nops(deqn) do
424: 		if type(deqn[i],`+`) then
425: 			deq := deqn[i]:
426: 		fi:
427: 	od:
428: else
429: 	deq := deqn:
430: fi:
431: 
432: deq := subs({seq(diff(F(z),z$i)=D^i,i=1..nops(deq))},deq):
433: 
434: poly := coeff(deq,D,degree(deq,D)):
435: 
436: sols := {solve(poly,z)} minus {0}:
437: 
438: return 1/min(seq(abs(sols[i]),i=1..nops(sols))):
439: 
440: 
441: 
442: 
443: 
444: 
445: end:
446: 
447: 
448: 
449: 
450: 
451: 
452: 
453: 
454: 
455: #FE(ope) given the denominator of the rational generating function calculates the free energy
456: FE := proc(ope) local i,approx,z,soln:
457: 
458: approx := solve(ope):
459: 
460: if nops({approx})>1 then
461: 	soln := seq(abs(Re(evalf(approx[i]))),i=1..nops({approx})):
462: else
463: 	soln := approx:
464: fi:
465: 
466: return log(1/min(soln)):
467: 
468: end:
469: 
470: 
471: 
472: #plotFE(Steps,winit,wfin) plots the free energies from w=winit to w=wfin using listplot
473: plotFE := proc(Steps,winit,wfin) local i,llist,w,ope,asymp,F,z:
474: 
475: 
476: llist := [seq([w,FE(denom(rigorgf(Steps,w,z)))],w=winit..wfin)]:
477: 
478: print(llist):
479: 
480: ope := RGF2D(Steps,z,F):
481: 
482: asymp := Asy(ope,F,z):
483: 
484: print(`The asymptotic value is`,evalf(log(asymp))):
485: 
486: listplot(llist,labels=["Width","Free Energy"]):
487: 
488: end:
489: 
490: 
491: 
492: #plotFEWE(Steps,w,tmin,tmax,smin,smax) given the steps Steps, width w and weight enumerators t,s calculates the free energy using Asy in GuessHolo2
493: plotFEWE := proc(Steps,w,tmin,tmax,smin,smax) local i,j,walks,ope,approx,z,Z,t,s:
494: 
495: 
496: approx := [seq([seq(FE(denom(rigorgfWE(Steps,w,z,i,j))),j=smin..smax)],i=tmin..tmax)]:
497: 
498: #return approx:
499: 
500: listplot3d(approx,labels=["t","s","Free Energy"],axes=boxed,orientation=[-74,73]):
501: 
502: end:
503: 
504: 
505: #ForceWE(Steps,w,tmin,tmax,smin,smax) calculates the numerical value of the force for width w and values of t and s
506: ForceWE := proc(Steps,w,tmin,tmax,smin,smax) local t,s,ope1,ope2,z,Z,approx1,approx2:
507: 
508: ope1 := rigorgfWE(Steps,w,z,j,i):
509: 
510: ope2 := rigorgfWE(Steps,w+1,z,j,i):
511: 
512: approx1 := [seq([seq(FE(subs({j=t,i=s},denom(ope1))),s=smin..smax)],t=tmin..tmax)]:
513: 
514: 
515: approx2 := [seq([seq(FE(subs({j=t,i=s},denom(ope2))),s=smin..smax)],t=tmin..tmax)]:
516: 
517: listplot3d(approx2-approx1,labels=["t","s","Force"],axes=boxed,orientation=[-74,73]):
518: 
519: end:
520: 
521: 
522: 
523: 
524: 
525: #plotinfFEWE(Steps,tmin,tmax) plots the free energy in the infinite width case in the given range of t.
526: plotinfFEWE := proc(Steps,tmin,tmax) local llist,i,j,t,s,n,w:
527: 
528: #Far off point from the origin
529: n := 100:
530: 
531: #High enough width to get reasonable answers
532: w := 1000:
533: 
534: llist := [seq([t,evalf(log(WEpolymer(Steps,[n+1,n+1],w,t,s)/WEpolymer(Steps,[n,n],w,t,s)))],t=tmin..tmax)]:
535: 
536: 
537: #eqn := RGF2DWE(Steps,z,H,t):
538: #llist := [seq([t,evalf(log(Asy(RGF2DWE(Steps,z,H,t),H,z)))],t=tmin..tmax)]:
539: 
540: 
541: listplot(llist,labels=["t","Free Energy"]):
542: 
543: end:
544: 
545: 
546: 
547: 
548: 
549: #anmat(M,DEGREE,ORDER,n,N) given a list of lists M tries to find a holonomic ansatz for the non-zero part of the columns, ie considering the coefficient of N^0,N^1,etc.
550: anmat := proc(M,DEGREE,ORDER,n,N) local i,j,k,l,x,ans,sol,rl,cl,marker:
551: 
552: 
553: rl := nops(M):
554: cl := nops(M[1]):
555: 
556: sol := []:
557: #marker[i] is the location in the i'th column of the location where the first non-zero term occurs
558: marker := []:
559: 
560: for i from 1 to cl do
561: 	for j from 1 to rl-1 do
562: 
563: 		if M[1][i] <> 0 then
564: 			marker := [op(marker),1]:
565: 			break:
566: 		fi:
567: 
568: 		if M[rl-1][i] = 0 and M[rl][i] = 0 then
569: 			marker := [op(marker),rl]:
570: 			break:
571: 		fi:
572: 
573: 		if M[j][i] = 0 and M[j+1][i] <> 0 then
574: 			marker := [op(marker),j+1]:
575: 			break:
576: 		fi:
577: 		
578: 	od:
579: od:
580: 
581: #return marker:
582: 
583: 
584: for k from 1 to cl do
585: 	
586: 	x := 0:
587: 	
588: 	for i from 1 to ORDER do
589: 		for j from 0 to DEGREE do
590: 
591: 			if x = 0 and (1+DEGREE)*(1+ORDER)+5+ORDER <= rl-marker[k] then
592: 				ans := findrec( [seq(M[marker[k]+l][k],l=0..rl-marker[k])], j,i,n,N):
593: 				if ans <> FAIL then
594: 					sol := [op(sol),ans]:
595: 					x := 1:
596: 				fi:
597: 				if j = DEGREE and i = ORDER and ans = FAIL then
598: 					print(`Need a higher DEGREE/ORDER for a solution for N^`,k-1):
599: 					x := 1:
600: 				fi:
601: 			fi:
602: 
603: 		od:
604: 	od:
605: od:
606: 
607: return sol:
608: 
609: end:
610: 
611: 
612: #rigorgf(Steps,w,z) calculates the generating function of walks with Steps and width w
613: rigorgf := proc(Steps,w,z) local i,j,temp,scri,eqs,var,sol:
614: 
615: eqs := {}:
616: 
617: for i from 1 to w+1 do
618: 
619: 	temp := scri[i]:
620: 
621: 	for j from 1 to nops(Steps) do
622: 		if i+Steps[j][2]-Steps[j][1] <= w+1 and i+Steps[j][2]-Steps[j][1] >=1 then
623: 			temp := temp- z^Steps[j][2]*scri[i+Steps[j][2]-Steps[j][1]]:
624: 		fi:
625: 	od:
626: 
627: 	if i = 1 then
628: 		temp := temp -1:
629: 	fi:
630: 
631: 	eqs := eqs union {temp}:
632: od:
633: 
634: var := {}:
635: 
636: for i from 1 to w+1 do
637: 	var := var union {scri[i]}:
638: od:
639: 
640: sol := subs(solve(eqs,var),scri[1]):
641: 
642: 
643: #print(`The first few terms of the Taylor series of the solution`):
644: #print(`are`, seq(coeftayl(sol,z=0,n),n=0..10)):
645: #print(`And the first few terms are precisely`):
646: #print(seq(polymer(Steps,[n,n],w),n=0..10)):
647: 
648: return sol:
649: 
650: end:
651: 
652: #rigorgfWE(Steps,w,z,t,s) calculates the generating function of walks with Steps and width w
653: rigorgfWE := proc(Steps,w,z,t,s) local i,j,temp,scri,eqs,var:
654: 
655: eqs := {}:
656: 
657: for i from 1 to w+1 do
658: 
659: 	temp := scri[i]:
660: 
661: 	for j from 1 to nops(Steps) do
662: 		if i+Steps[j][2]-Steps[j][1] <= w+1 and i+Steps[j][2]-Steps[j][1] >=1 then
663: 			if i = 1 then
664: 				temp := temp- t*z^Steps[j][2]*scri[i+Steps[j][2]-Steps[j][1]]:
665: 			elif i=w+1 then
666: 				temp := temp- s*z^Steps[j][2]*scri[i+Steps[j][2]-Steps[j][1]]:
667: 			else
668: 				temp := temp- z^Steps[j][2]*scri[i+Steps[j][2]-Steps[j][1]]:
669: 			fi:
670: 		fi:
671: 	od:
672: 
673: 	if i = 1 then
674: 		temp := temp -1:
675: 	fi:
676: 
677: 	eqs := eqs union {temp}:
678: od:
679: 
680: #return eqs:
681: 
682: var := {}:
683: 
684: for i from 1 to w+1 do
685: 	var := var union {scri[i]}:
686: od:
687: 
688: #return solve(eqs,var):
689: return subs(solve(eqs,var),scri[1]):
690: 
691: end:
692: 	
693: 
694: #RGF2D(Steps,z,F) finds the rigorous generating function for an arbitrary sequence of steps with infinite width
695: RGF2D:= proc(Steps, z, F) local i,j,k,G,vars,eqs,maxL,temp,num,sol,diffop,recop:
696: 
697: num := nops(Steps):
698: 
699: maxL := 0:
700: 
701: for i from 1 to num do
702: 	if abs(Steps[i][1]-Steps[i][2]) > maxL+1 then
703: 		maxL := abs(Steps[i][1]-Steps[i][2])-1:
704: 	fi:
705: od:
706: 
707: eqs := F[1][1]-1-G[1][1]*F[1][1]:
708: 
709: for i from 1 to nops(Steps) do
710: 	if Steps[i][1] = Steps[i][2] then
711: 		eqs := eqs-z^Steps[i][1]*F[1][1]:
712: 	fi:
713: od:
714: 
715: eqs := {eqs}:
716: 
717: temp := G[1][1]:
718: for i from 1 to num do
719: 	for j from 1 to num do
720: 		if Steps[i][1] > Steps[i][2] and Steps[j][1] < Steps[j][2] then
721: 			temp := temp - z^(Steps[j][2]+Steps[i][2])*F[abs(Steps[i][1]-Steps[i][2])][abs(Steps[j][1]-Steps[j][2])]:
722: 		fi:
723: 	od:
724: od:
725: eqs := eqs union {temp}:
726: 
727: 
728: for i from 1 to maxL+1 do
729: 	for j from 1 to maxL+1 do
730: 		if i <> 1 and j <> 1 then
731: 			if i >= j then
732: 				eqs := eqs union {G[i][j]-G[i-j+1][1]}:
733: 			else
734: 				eqs := eqs union {G[i][j]-G[1][j-i+1]}:
735: 			fi:
736: 
737: 		fi:
738: 	od:
739: od:
740: 
741: 
742: for i from 1 to maxL+1 do
743: 	for j from 1 to maxL+1 do
744: 	if i <> j then
745: 		if i <> 1 or j <> 1 then
746: 			temp := F[i][j]:
747: 			for k from  1 to min(i,j) do
748: 				if i < j then
749: 					temp := temp - F[i-k+1][1]*G[k][j]:
750: 				else 
751: 					temp := temp - G[i][k]*F[1][j-k+1]:
752: 				fi:
753: 			od:
754: 
755: 			eqs := eqs union {temp}:
756: 		fi:
757: 	fi:
758: 	od:
759: od:
760: 
761: for k from 2 to maxL+1 do
762:         temp := F[k][k]-F[1][1]:
763:         for i from 2 to k do
764:                 temp := temp - G[k-i+2][1]*F[1][k-i+2]:
765:         od:
766:         eqs := eqs union {temp}:
767: od:
768: 
769: 
770: for k from 2 to maxL+1 do
771: 	temp := G[1][k]:
772: 	for i from 1 to num do
773: 		if Steps[i][1] > Steps[i][2] then
774: 			temp := temp - z^Steps[i][2]*F[abs(Steps[i][1]-Steps[i][2])][k-1]:
775: 		fi:
776: 	od:
777: 	eqs := eqs union {temp}:
778: od:
779: 
780: 
781: for k from 2 to maxL+1 do
782: 	temp := G[k][1]:
783: 	for i from 1 to num do
784: 		if Steps[i][1] < Steps[i][2] then
785: 			temp := temp - z^Steps[i][2]*F[k-1][abs(Steps[i][1]-Steps[i][2])]:
786: 		fi:
787: 	od:
788: 	eqs := eqs union {temp}:
789: od:
790: 
791: vars := {}:
792: 
793: for i from 1 to maxL+1 do
794: 	for j from 1 to maxL+1 do
795: 		vars := vars union {F[i][j],G[i][j]}:
796: 	od:
797: od:
798: 
799: vars := vars minus {F[1][1]}:
800: sol := eliminate(eqs,vars):
801: 
802: if nops({sol}) > 1 then
803: 	return seq(subs(F[1][1]=F,sol[i][2]),i=1..nops({sol})):
804: else
805: 	return op(subs(F[1][1]=F,sol[2])):
806: fi:
807: 
808: 
809: end:
810: 
811: 
812: 
813: 
814: 
815: 
816: #RGF2DWE(Steps,z,F,t) finds the rigorous generating function for an arbitrary sequence of steps with infinite width and variable t counting the number of times the walk touches the line y=x.
817: RGF2DWE:= proc(Steps, z, H,t) local i,j,k,G,vars,eqs,maxL,temp,num,sol,diffop,recop:
818: 
819: num := nops(Steps):
820: 
821: maxL := 0:
822: 
823: for i from 1 to num do
824: 	if abs(Steps[i][1]-Steps[i][2]) > maxL+1 then
825: 		maxL := abs(Steps[i][1]-Steps[i][2])-1:
826: 	fi:
827: od:
828: 
829: eqs := F[1][1]-1-G[1][1]*F[1][1]:
830: 
831: for i from 1 to nops(Steps) do
832: 	if Steps[i][1] = Steps[i][2] then
833: 		eqs := eqs-z^Steps[i][1]*F[1][1]:
834: 	fi:
835: od:
836: 
837: eqs := {eqs}:
838: 
839: temp := G[1][1]:
840: for i from 1 to num do
841: 	for j from 1 to num do
842: 		if Steps[i][1] > Steps[i][2] and Steps[j][1] < Steps[j][2] then
843: 			temp := temp - z^(Steps[j][2]+Steps[i][2])*F[abs(Steps[i][1]-Steps[i][2])][abs(Steps[j][1]-Steps[j][2])]:
844: 		fi:
845: 	od:
846: od:
847: eqs := eqs union {temp}:
848: 
849: 
850: for i from 1 to maxL+1 do
851: 	for j from 1 to maxL+1 do
852: 		if i <> 1 and j <> 1 then
853: 			if i >= j then
854: 				eqs := eqs union {G[i][j]-G[i-j+1][1]}:
855: 			else 
856: 				eqs := eqs union {G[i][j]-G[1][j-i+1]}:
857: 			fi:
858: 
859: 		fi:
860: 	od:
861: od:
862: 
863: 
864: for i from 1 to maxL+1 do
865: 	for j from 1 to maxL+1 do
866: 	if i <> j then
867: 		if i <> 1 or j <> 1 then
868: 			temp := F[i][j]:
869: 			for k from  1 to min(i,j) do
870: 				if i < j then
871: 					temp := temp - F[i-k+1][1]*G[k][j]:
872: 				else 
873: 					temp := temp - G[i][k]*F[1][j-k+1]:
874: 				fi:
875: 			od:
876: 
877: 			eqs := eqs union {temp}:
878: 		fi:
879: 	fi:
880: 	od:
881: od:
882: 
883: for k from 2 to maxL+1 do
884:         temp := F[k][k]-F[1][1]:
885:         for i from 2 to k do
886:                 temp := temp - G[k-i+2][1]*F[1][k-i+2]:
887:         od:
888:         eqs := eqs union {temp}:
889: od:
890: 
891: 
892: for k from 2 to maxL+1 do
893: 	temp := G[1][k]:
894: 	for i from 1 to num do
895: 		if Steps[i][1] > Steps[i][2] then
896: 			temp := temp - z^Steps[i][2]*F[abs(Steps[i][1]-Steps[i][2])][k-1]:
897: 		fi:
898: 	od:
899: 	eqs := eqs union {temp}:
900: od:
901: 
902: 
903: for k from 2 to maxL+1 do
904: 	temp := G[k][1]:
905: 	for i from 1 to num do
906: 		if Steps[i][1] < Steps[i][2] then
907: 			temp := temp - z^Steps[i][2]*F[k-1][abs(Steps[i][1]-Steps[i][2])]:
908: 		fi:
909: 	od:
910: 	eqs := eqs union {temp}:
911: od:
912: 
913: 
914: temp := H-1:
915: 
916: for i from 1 to nops(Steps) do
917: 	if Steps[i][1] = Steps[i][2] then
918: 		temp := temp-t*z^Steps[i][1]*H:
919: 	fi:
920: od:
921: 
922: for i from 1 to num do
923: 	for j from 1 to num do
924: 		if Steps[i][1] > Steps[i][2] and Steps[j][1] < Steps[j][2] then
925: 			temp := temp - t*z^(Steps[j][2]+Steps[i][2])*F[abs(Steps[i][1]-Steps[i][2])][abs(Steps[j][1]-Steps[j][2])]*H:
926: 		fi:
927: 	od:
928: od:
929: 
930: eqs := eqs union {temp}:
931: 
932: 
933: vars := {}:
934: 
935: for i from 1 to maxL+1 do
936: 	for j from 1 to maxL+1 do
937: 		vars := vars union {F[i][j],G[i][j]}:
938: 	od:
939: od:
940: 
941: sol := eliminate(eqs,vars):
942: 
943: return op(sol[2]):
944: 
945: if nops({sol}) > 1 then
946: 	return seq(subs(sol[i],H),i=1..nops({sol})):
947: else
948: 	return subs(sol,H):
949: fi:
950: 
951: end:
952: 
953: 
954: 
955: 
956: 
957: 
958: 
959: 
960: 
961: 
962: 
963: 
964: 
965: 
966: 
967: 
968: 
969: 
970: 
971: 
972: 
973: 
974: 
975: 
976: 
977: 
978: 
979: #rgfprove(Steps,ope,W,N) "proves" that ope(W,N) actually holds for arbitrary w by looking at the generating functions
980: rgfprove:= proc(Steps,ope,W,N) local i,j,k,l,F,G,vars,eqs,maxL,temp,temp1,n,sol,sol2,ans,deg:
981: 
982: #What the answer should look like: replay W^max ->1, W^(max-1)->F[1], W^(max-2) ->F[1]F[2], ... , etc.
983: ans := 0:
984: 
985: _EnvAllSolutions := true:
986: 
987: for i from 1 to nops(ope) do
988: 	deg := degree(op(i,ope),W):
989: 	ans := ans + coeff(op(i,ope),W,deg)*mul(F[j][1][1],j=1..degree(ope,W)-deg):
990: od:
991: 
992: print(`The solution to be proved is:`,ans,`=0`):
993: 
994: n := nops(Steps):
995: 
996: maxL := 0:
997: 
998: for i from 1 to n do
999: 	if abs(Steps[i][1]-Steps[i][2]) > maxL+1 then
1000: 		maxL := abs(Steps[i][1]-Steps[i][2])-1:
1001: 	fi:
1002: od:
1003: 
1004: eqs := F[1][1][1]-1-G[1][1][1]*F[1][1][1]:
1005: 
1006: for i from 1 to nops(Steps) do
1007: 	if Steps[i][1] = Steps[i][2] then
1008: 		eqs := eqs-N^Steps[i][1]*F[1][1][1]:
1009: 	fi:
1010: od:
1011: 
1012: eqs := {eqs}:
1013: 
1014: temp := G[1][1][1]:
1015: for i from 1 to n do
1016: 	for j from 1 to n do
1017: 		if Steps[i][1] > Steps[i][2] and Steps[j][1] < Steps[j][2] then
1018: 			temp := temp - N^(Steps[j][2]+Steps[i][2])*F[2][abs(Steps[i][1]-Steps[i][2])][abs(Steps[j][1]-Steps[j][2])]:
1019: 		fi:
1020: 	od:
1021: od:
1022: eqs := eqs union {temp}:
1023: 
1024: 
1025: for i from 1 to maxL+1 do
1026: 	for j from 1 to maxL+1 do
1027: 		if i <> 1 and j <> 1 then
1028: 			if i >= j then
1029: 				eqs := eqs union {G[1][i][j]-G[i][i-j+1][1]}:
1030: 			else
1031: 				eqs := eqs union {G[1][i][j]-G[j][1][j-i+1]}:
1032: 			fi:
1033: 
1034: 		fi:
1035: 	od:
1036: od:
1037: 
1038: 
1039: for i from 1 to maxL+1 do
1040: 	for j from 1 to maxL+1 do
1041: 	if i <> j then
1042: 		if i <> 1 or j <> 1 then
1043: 			temp := F[1][i][j]:
1044: 			for k from  1 to min(i,j) do
1045: 				if i < j then
1046: 					temp := temp - F[1][i-k+1][1]*G[1][k][j]:
1047: 				else 
1048: 					temp := temp - G[1][i][k]*F[1][1][j-k+1]:
1049: 				fi:
1050: 			od:
1051: 
1052: 			eqs := eqs union {temp}:
1053: 		fi:
1054: 	fi:
1055: 	od:
1056: od:
1057: 
1058: for k from 2 to maxL+1 do
1059:         temp := F[1][k][k]-F[k][1][1]:
1060:         for i from 2 to k do
1061:                 temp := temp - G[i-1][k-i+2][1]*F[i-1][1][k-i+2]:
1062:         od:
1063:         eqs := eqs union {temp}:
1064: od:
1065: 
1066: 
1067: for k from 2 to maxL+1 do
1068: 	temp := G[1][1][k]:
1069: 	for i from 1 to n do
1070: 		if Steps[i][1] > Steps[i][2] then
1071: 			if k-1 < abs(Steps[i][1]-Steps[i][2]) then
1072: 				temp := temp - N^Steps[i][2]*F[2][abs(Steps[i][1]-Steps[i][2])-k+2][1]:
1073: 			else
1074: 				temp := temp - N^Steps[i][2]*F[2][abs(Steps[i][1]-Steps[i][2])][k-1]:
1075: 			fi:
1076: 		fi:
1077: 	od:
1078: 	eqs := eqs union {temp}:
1079: od:
1080: 
1081: 
1082: for k from 2 to maxL+1 do
1083: 	temp := G[1][k][1]:
1084: 	for i from 1 to n do
1085: 		if Steps[i][1] < Steps[i][2] then
1086: 			if k-1 < abs(Steps[i][1]-Steps[i][2]) then
1087: 				temp := temp - N^Steps[i][2]*F[2][1][abs(Steps[i][1]-Steps[i][2])-k+2]:
1088: 			else
1089: 				temp := temp - N^Steps[i][2]*F[2][k-1][abs(Steps[i][1]-Steps[i][2])]:
1090: 			fi:
1091: 		fi:
1092: 	od:
1093: 	eqs := eqs union {temp}:
1094: od:
1095: 
1096: 
1097: vars := {}:
1098: 
1099: for i from 1 to maxL+1 do
1100: 	for j from 1 to maxL+1 do
1101: 		for k from 1 to maxL+1 do
1102: 			vars := vars union {G[k][i][j]}:
1103: 		od:
1104: 	od:
1105: od:
1106: 
1107: sol := eliminate(eqs,vars)[2]:
1108: 
1109: print(`The relation among various generating functions is`):
1110: print(sol):
1111: print(`with the following convention for F[i][j][k]: i stands for the symbolic width w-i+1`):
1112: print(`and j and k stand for the [j-1,k-1] walk`):
1113: 
1114: sol2 := sol:
1115: 
1116: for l from 1 to degree(ope,W)-1 do
1117: 
1118: 	for i from 1 to nops(sol) do
1119: 		temp := 0:
1120: 		for j from 1 to nops(sol[i]) do
1121: 			temp1 := 1:
1122: 			if nops(op(j,sol[i]))  > 1 then
1123: 				for k from 1 to nops(op(j,sol[i])) do
1124: 					if type(op(k,op(j,sol[i])),indexed) then
1125: 						temp1 := temp1*incby1(op(k,op(j,sol[i]))):
1126: 					else
1127: 						temp1 := temp1*op(k,op(j,sol[i])):
1128: 					fi:
1129: 				od:
1130: 			elif type(op(j,sol[i]),indexed) then
1131: 				temp1 := temp1*incby1(op(j,sol[i])):
1132: 			fi:
1133: 				
1134: 			temp := temp + temp1:
1135: 		od:
1136: 		sol2 := sol2 union {temp}
1137: 	od:	
1138: 	sol := sol2 minus sol:
1139: od:
1140: 
1141: vars := {}:
1142: 
1143: for i from 1 to maxL+1 do
1144: 	for j from 1 to maxL+1 do
1145: 		for k from 1 to degree(ope,W) do
1146: 			vars := vars union {F[k][i][j]}:
1147: 		od:
1148: 	od:
1149: od:
1150: 
1151: vars := vars minus {seq(F[i][1][1],i=1..degree(ope,W)),seq(seq(F[1][i][j],i=2..maxL+2),j=2..maxL+1)}:
1152: 
1153: sol := solve(sol2):
1154: 
1155: #return sol:
1156: 
1157: print(`Using many copies of the above equations with different widths, solving for them`):
1158: print(`And substituting them in the expected solution gives:`):
1159: 
1160: return {seq(simplify(subs(sol[i],ans)),i=1..nops({sol}))};
1161: 
1162: end:
1163: 
1164: 
1165: incby1 := proc(F) local i,j,k,temp:
1166: 
1167: temp := op(0,op(0,op(0,F))):
1168: i := op(1,op(0,op(0,F)))+1:
1169: j := op(1,op(0,F)):
1170: k := op(1,F):
1171: 
1172: return temp[i][j][k]:
1173: 
1174: end:
1175: 
1176: 
1177: 
1178: 
1179: 
1180: 
1181: 
1182: 
1183: 
1184: 
1185: 
1186: 
1187: 
1188: 
1189: 
1190: 
1191: 
1192: 
1193: 
1194: 
1195: 
1196: 
1197: ##################Functions from GuessHolo2: findrec() and Yafe()
1198: #findrec(f,DEGREE,ORDER,n,N): guesses a recurrence operator annihilating
1199: #the sequence f of degree DEGREE and order ORDER
1200: #For example, try: findrec([seq(i,i=1..10)],0,2,n,N);
1201: findrec:=proc(f,DEGREE,ORDER,n,N)
1202: local ope,var,eq,i,j,n0,kv,var1,eq1,mu,a,dim:
1203: option remember:
1204: 
1205: dim := LinearAlgebra[Dimension](f);
1206: if (1+DEGREE)*(1+ORDER)+5+ORDER>dim then
1207: error "Insufficient data for a recurrence of order %1 degree %2",ORDER, DEGREE:
1208: fi:
1209: ope:=0:
1210: var:={}:
1211: 
1212: ope := add( add(a[i,j]*n^j*N^i, j=0..DEGREE), i=0..ORDER);
1213: var := indets(ope) minus {n,N};
1214: 
1215: eq := {seq(
1216:   add(subs(n=n0,coeff(ope,N,i))*f[n0+i], i=0..ORDER),
1217:   n0 = 1..dim-ORDER)};
1218: 
1219: var1:=solve(eq,var):
1220: 
1221: kv := map(lhs, select( x->evalb(op(1,x) = op(2,x)), var1));
1222: 
1223: ope:=eval(ope, var1);
1224: if ope=0 then return FAIL end if;
1225: 
1226: ope:={seq(coeff(expand(ope),kv[i],1),i=1..nops(kv))} minus {0}:
1227: 
1228: `if`( nops(ope)>=1,Yafe(ope[1],N)[2],FAIL);
1229: end:
1230: 
1231: 
1232: 
1233: Yafe:=proc(ope,N) local i,ope1,coe1,L:
1234:     if ope=0 then return (1,0) end if;
1235:     ope1:=expand(ope):
1236:     L:=degree(ope1,N):
1237:     coe1:=coeff(ope1,N,L):
1238:     ope1:=normal(ope1/coe1):
1239:     # ope1:=normal(ope1):
1240:     ope1 := collect(ope1, N, factor);
1241:     factor(coe1),ope1:
1242: end:
1243: 
1244: 
1245: 
1246: 
1247: