###################################################################### ##MARKOV: Save this file as MARKOV. To use it, stay in the # ##same directory, get into Maple (by typing: maple ) # ##and then type: read MARKOV : # ##Then follow the instructions given there # ## # ##Written by Doron Zeilberger, Temple University , # #zeilberg@math.temple.edu. # ####################################################################### #MARKOV: A PACKAGE FOR COMPUTING generating functions #and Series-Expansion for paths in Markov Chains #By Doron Zeilberger, Temple University #First Released: Jan. 7, 2000 #LAST UPDATE: Jan. 7, 2000 #The most current version is available from #http://www.math.temple.edu/~zeilberg/ #To use it get it first, call it `MARKOV` then go into Maple #by typing `maple`. Then, in Maple , type `read MARKOV;` #and see the help files by doing " ezra(); " and " ezra(function_name) "; print(`MARKOV: A PACKAGE FOR COUNTING PATHS IN COMBINATORIAL MARKOV CHAINS`): print(`Version of Jan. 7, 2000`): print(`written by Doron Zeilberger(zeilberg@math.temple.edu).`): print(`The most current version is always available from`): print(`http://www.math.temple.edu/~zeilberg/ `): print(`It is one of the numerous packages accompanying Doron Zeilberger's`): print( ` article: `): print(` "SYMBOL-CRUNCHING With The TRANSFER-MATRIX Method`): print(`With Applications to the Counting of`): print(` Skinny Physical Creatures" `): lprint(``): print(`For a list of the main procedures type "ezra();" .`): print(`For a list of ALL procedures type "ezra1();" , for help with`): print(`a specific procedure, type "ezra(procedure_name);"`): ezra:=proc() if args=NULL then print(` This is MARKOV, a Maple package for computing generating-`): print(` functions, and series-expansions, for paths in`): print(` Combinatorial Markov Chains `): print(`It is one of the numerous packages accompanying Doron Zeilberger's`): print( ` article: "Symbol-Crunching With the Transfer-Matrix Method `): print(`With Applications to the Counting of`): print(` Skinny Physical Creatures" `): print(` available from his homepage `): print(` For a list of all procedurs type: " ezra1(); " `): print(``): print(`The MAIN PROCEDURES are : `): print(` `): print(`SolveMC1,SolveMC1series`): print(`SolveMC2,SolveMC2series`): print(`SolveMC3,SolveMC3series`): print(`SolveMC4,SolveMC4series`): elif nops([args])=1 and op(1,[args])=KosherMC1 then print(`KosherMC1(MC): checks whether MC is (the profile) of`): print(`a Vertex-Weighted Simple Combinatorial Markov Chain `): print(` i.e. a Markov Chain of type I `): elif nops([args])=1 and op(1,[args])=KosherMC2 then print(`KosherMC2(MC): checks whether MC is (the profile) of`): print(`a Vertex-Weighted Non-Simple Combinatorial Markov Chain `): print(` i.e. a Markov Chain of type II `): elif nops([args])=1 and op(1,[args])=KosherMC3 then print(`KosherMC3(MC): checks whether MC is (the profile) of`): print(`an Edge-Weighted Simple Combinatorial Markov Chain `): print(` i.e. a Markov Chain of type III `): elif nops([args])=1 and op(1,[args])=KosherMC4 then print(`KosherMC4(MC,t): checks whether MC is (the profile) of`): print(`an Edge-Weighted Simple Combinatorial Markov Chain `): print(` i.e. a Markov Chain of type IV `): elif nops([args])=1 and op(1,[args])=SolveMC1 then print(`SolveMC1(MC,s): Given MC,(the profile) of a Vertex-Weighted`): print(` Simple (i.e. no multiple edges) Combinatorial Markov Chain,`): print(`and a variable s, computes the generating function, in the`): print(` variable s, whose coeff. of s^i is the number of paths `): print(` of weight i`): print(` The first argument MC, should be a list of length 4:`): print(`[Start,Finish,NeighborLists,WtList]`): print(`The number of vertices is nops(NeighborList)(let's call it N) `): print(`It is assumed that the vertices are labelled 1,..., N`): print(`Srart is the set of labels of vertices where a path may start`): print(`Finish is the set of labels of vertices where a path may end`): print(`NeighborLists is a list of sets, of length N, whose i^th item`): print(` is the set of vertices j such that there is (one and only) one edge`): print(`from i to j.`): print(`WtList is a list of length N, of positive integeres, such that`): print(`the i^th entry of WtList is the weight of the vertex labelled i`): print(``): print(`For example, try`): print(`SolveMC1([{1},{1},[{1}],[1]],t)`): print(``): print(` Once again the syntax is: SolveMC1(MC,s); `): elif nops([args])=1 and op(1,[args])=SolveMC2 then print(`SolveMC2(MC,s): Given MC,(the profile) of a Vertex-Weighted`): print(` Non-Simple (i.e. with multiple edges) Combinatorial Markov Chain,`): print(`and a variable s, computes the generating function, in the`): print(` variable s, whose coeff. of s^i is the number of paths`): print(` of weight i`): print(` The first argument MC, should be a list of length 4:`): print(`[Start,Finish,NeighborLists,WtList]`): print(`The number of vertices is nops(NeighborList)(let's call it N) `): print(`It is assumed that the vertices are labelled 1,..., N`): print(`Srart is the set of labels of vertices where a path may start`): print(`Finish is the set of labels of vertices where a path may end`): print(`NeighborLists is an N-list of multi-sets, whose i^th item`): print(` is the multi-set of vertices `): print(` given as {[a1,b1],[a2,b2],...}, where this means that there are`): print(` b1 edges between i and a1, b2 edges between i and a2, etc.`): print(`WtList is a list of length N, of positive integeres, such that`): print(`the i^th entry of WtList is the weight of the vertex labelled i`): print(``): print(`For example, try`): print(`SolveMC2([{1},{1},[{[1,1]}],[1]],t)`): print(``): print(` Once again the syntax is: SolveMC2(MC,s); `): elif nops([args])=1 and op(1,[args])=SolveMC3 then print(`SolveMC3(MC,s): Given MC,(the profile) of an Edge-Weighted`): print(` Simple (i.e. without multiple edges) Combinatorial Markov Chain,`): print(` i.e. of type III `): print(`and a variable s, computes the generating function, in the`): print(` variable s, whose coeff. of s^i is the number of paths`): print(` of weight i`): print(` The first argument MC, should be a list of length 3:`): print(`[Start,Finish,NeighborLists]`): print(`The number of vertices is nops(NeighborList)(let's call it N) `): print(`It is assumed that the vertices are labelled 1,..., N`): print(`Srart is the set of labels of vertices where a path may start`): print(`Finish is the set of labels of vertices where a path may end`): print(`NeighborLists is an N-list of sets, whose i^th item`): print(` is the set of vertices `): print(` given as {[a1,b1],[a2,b2],...}, where this means that there is`): print(` an edge between i and a1, whose weight is b1 `): print(` an edge between i and a2, whose weight is b2 `): print(` ... `): print(``): print(`For example, try`): print(`SolveMC3([{1},{1},[{[1,1]}]],t)`): print(``): print(` Once again the syntax is: SolveMC3(MC,s); `): elif nops([args])=1 and op(1,[args])=SolveMC4 then print(`SolveMC4(MC,t): Given a type-IV `): print(` Markov Chain [LeftLetters,RightLetters,`): print(` TransMatrix], `): print(` Let N:=nops(TransMatrix), the vertices are assumed to be labelled `): print(` by 1, ..., N `): print(` The second input is a variable t `): print(` and the first input, MC is list of length 3 `): print(``): print(` The 3 components of MC are as follows:`): print(``): print(` LeftLetters is the set of vertices where a path may start`): print(` RightLetters is the set of vertices where a path may end `): print(` TransMatrix is a list of sets, where TransMatrix[i] is the `): print(` set consisting of pairs [j, polyn], where the coeff. of `): print(` of t^k in polyn is the number of edges from i to j with weight k.`): print(``): print(` The output is the formal power series (necessarily a rational `): print(` function) whose coeff. of t^i is `): print(` the number of paths of weight i, that `): print(` start with a vertex of LeftLetters and ends with a vertex `): print(` of RightLetters, `): print(` Once again the syntax is: SolveMC4(MC,s); `): elif nops([args])=1 and op(1,[args])=SolveMC1series then print(`SolveMC1series(MC,L): Given a Markov Chain of type I, MC`): print(`and a positive integer L, outputs`): ptint(` The list of length L, whose i^th term`): print(`is the coefficient of s^i in SolveMC1(MC,s), for i=1..L`): elif nops([args])=1 and op(1,[args])=SolveMC2series then print(`SolveMC2series(MC,L): Given a Markov Chain of type II, MC`): print(`and a positive integer L, outputs`): ptint(` The list of length L, whose i^th term`): print(`is the coefficient of s^i in SolveMC2(MC,s), for i=1..L`): elif nops([args])=1 and op(1,[args])=SolveMC3series then print(`SolveMC3series(MC,L): Given a Markov Chain of type III, MC`): print(`and a positive integer L, outputs`): ptint(` The list of length L, whose i^th term`): print(`is the coefficient of s^i in SolveMC3(MC,s), for i=1..L`): elif nops([args])=1 and op(1,[args])=SolveMC4series then print(`SolveMC4series(MC,t,L): Given a Markov Chain of type IV, MC`): print(`and a positive integer L, outputs`): ptint(` The list of length L, whose i^th term`): print(`is the coefficient of t^i in SolveMC4(MC,t), for i=1..L`): elif nops([args])=1 and op(1,[args])=SolveMC1seriesS then print(`SolveMC1seriesS(MC,L,s): The first L terms in the sequence`): print(`weight-enumerating the number of words of weight n (or t^n)`): print(`also according to the weigth: s^(number of letters)`): print(`(depending on your def. of weight) in the Markov`): print(`Chain [LeftLetters,RightLetters,NeighborLists,WtList]`): print(`that start in one of the left-letters and ends in`): print(`one of the right-letters`): elif nops([args])=1 and op(1,[args])=SolveMC2seriesS then print(`SolveMC2seriesS(MC,L,s): The first L terms in the sequence`): print(`weight-enumerating the number of paths of weight n (or t^n)`): print(`also according to the weigth: s^(length of paths))`): print(` in the Combinatorial Markov`): print(`Chain of type II [LeftLetters,RightLetters,NeighborLists,WtList]`): elif nops([args])=1 and op(1,[args])=SolveMC3seriesS then print(`SolveMC3seriesS(MC,L,s): The first L terms in the sequence`): print(`weight-enumerating the number of paths of weight n (or t^n)`): print(`also according to the weigth: s^(length of paths))`): print(` in the Combinatorial Markov`): print(`Chain of type III [LeftLetters,RightLetters,NeighborLists]`): elif nops([args])=1 and op(1,[args])=SolveMC4seriesS then print(`SolveMC4seriesS(MC,t,L,s): The first L terms in the sequence`): print(`weight-enumerating the number of paths of weight n (or t^n)`): print(`also according to the weigth: s^(number of letters)`): print(`(depending on your def. of weight) in the Combinatorial Markov`): print(`Chain of type IV: [LeftLetters,RightLetters,NeighborLists]`): else print(`There is no ezra item for`,args[1]): fi: end: ezra1:=proc() if args=NULL then print(` For help with a specific procedurs type: "ezra(proc_name);" `): print(` NOT: ezra1(proc_name); `): print(``): print(`The PROCEDURES here are : `): print(`KosherMC1, SolveMC1,SolveMC1series,SolveMC1seriesS`): print(`KosherMC2, SolveMC2,SolveMC2series,SolveMC2seriesS`): print(`KosherMC3, SolveMC3,SolveMC3series, SolveMC3seriesS`): print(`KosherMC4, SolveMC4,SolveMC4series, SolveMC4seriesS`): else print(`Cant's take no-empty input`): fi: end: #############SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE I ###(Vertex-Weighted, with NO multiple-edges #KosherMC1(MC): checks whether MC is (the profile) of #a Vertex-Weighted Simple Combinatorial Markov Chain KosherMC1:=proc(MC) local LL,RL,Nei,Wts,N,i,kv: if not type (MC,list) then print(`The input should be a list`): RETURN(false): fi: if nops(MC)<>4 then print(`The input should be a 4-list`): RETURN(false): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: if not type(LL,set) then print(LL,`should be a set`): RETURN(false): fi: if not type(RL,set) then print(RL,`should be a set`): RETURN(false): fi: if not type(Nei,list) then print(Nei, `should be a list`): fi: if not type(Wts,list) then print(`The fourth item of the input-list should be a list`): RETURN(false): fi: N:=nops(Nei): kv:={seq(i,i=1..N)}: if LL minus kv<>{} then print(LL, `should be a subset of`,kv): RETURN(false): fi: if RL minus kv<>{} then print(RL, `should be a subset of`,kv): RETURN(false): fi: for i from 1 to nops(Nei) do if not type(Nei[i],set) then print(`The `, i, `-th item of the third item should be a set`): RETURN(false): fi: if Nei[i] minus kv<>{} then print(`The `, i, `-th item of the third item should be a subset of`): print(kv): RETURN(false): fi: od: if not type(Wts,list) then print(`The fourth item of the input-list should be a list`): RETURN(false): fi: if nops(Wts)<>N then print(`The fourth (and last) item in the input-list should be`): print(`of the same length as the third item`): RETURN(false): fi: for i from 1 to nops(Wts) do if not (type(Wts[i],integer) and Wts[i]>0) then print(`The `, i, `-th entry in the 4th item of the input list`, Wts[i]): print(`should be a positive integer `): RETURN(false): fi: od: true: end: #SolveMC1(MC,s): The generating function for all paths #on the Markov-Chain of type I, MC, in the variable s #see ezra(SolveMC1) for more details SolveMC1:=proc(MC,s) local eq,var,i,LL,RL,Nei,Wts,N,eq1,A,lu,j,Sakh,mu: if not KosherMC1(MC) then ERROR(`Bad input`): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): eq:={}: var:={}: for i from 1 to N do var:=var union {A[i]}: if member(i,RL) then eq1:=A[i]-s^Wts[i]: else eq1:=A[i]: fi: lu:=0: Sakh:=Nei[i]: for j from 1 to nops(Sakh) do lu:=lu+A[Sakh[j]]: od: eq1:=eq1-s^Wts[i]*lu: eq:=eq union {eq1}: od: var:=solve(eq,var): mu:=0: for i from 1 to nops(LL) do mu:=mu+subs(var,A[LL[i]]): od: normal(mu): end: #SolveMC1series(MC,L): The first L terms in the sequence #enumerating the number of words of weight n (or t^n) #(depending on your def. of weight) in the Markov #Chain [LeftLetters,RightLetters,NeighborLists,WtList] #that start in one of the left-letters and ends in #one of the right-letters SolveMC1series:=proc(MC,L) local LL,RL,Nei,Wts,N,MW,A,TOT,cur,Sakh,i,j,k,tot,sa: if not KosherMC1(MC) then ERROR(`Bad input`): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): MW:=max(op(Wts)): TOT:=[]: for i from 1 to N do A[i]:=[seq(0,j=1..MW)]: od: for j from 1 to L do for i from 1 to N do if member(i,RL) and Wts[i]=j then cur[i]:=1: else cur[i]:=0: fi: Sakh:=Nei[i]: for k from 1 to nops(Sakh) do sa:=Sakh[k]: cur[i]:=cur[i]+A[sa][MW-Wts[i]+1]: od: od: tot:=0: for i from 1 to nops(LL) do tot:=tot+cur[LL[i]]: od: TOT:=[op(TOT),tot]: for i from 1 to N do A[i]:=[op(2..MW,A[i]),cur[i]]: od: od: TOT: end: #SolveMC1seriesS(MC,L,s): The first L terms in the sequence #weight-enumerating the number of words of weight n (or t^n) #(depending on your def. of weight) in the Markov #Chain [LeftLetters,RightLetters,NeighborLists,WtList] #that start in one of the left-letters and ends in #one of the right-letters #according to the weight: number of letters SolveMC1seriesS:=proc(MC,L,s) local LL,RL,Nei,Wts,N,MW,A,TOT,cur,Sakh,i,j,k,tot,sa: if not KosherMC1(MC) then ERROR(`Bad input`): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): MW:=max(op(Wts)): TOT:=[]: for i from 1 to N do A[i]:=[seq(0,j=1..MW)]: od: for j from 1 to L do for i from 1 to N do if member(i,RL) and Wts[i]=j then cur[i]:=s: else cur[i]:=0: fi: Sakh:=Nei[i]: for k from 1 to nops(Sakh) do sa:=Sakh[k]: cur[i]:=expand(cur[i]+s*A[sa][MW-Wts[i]+1]): od: od: tot:=0: for i from 1 to nops(LL) do tot:=tot+cur[LL[i]]: od: TOT:=[op(TOT),tot]: for i from 1 to N do A[i]:=[op(2..MW,A[i]),cur[i]]: od: od: TOT: end: #####END SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE I #############SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE II ###(Vertex-Weighted, with multiple-edges) #KosherMC2(MC): checks whether MC is (the profile) of #type II (a Vertex-Weighted Non-Simple Combinatorial Markov Chain) KosherMC2:=proc(MC) local LL,RL,Nei,Wts,N,i,kv,lu,i1: if not type (MC,list) then print(`The input should be a list`): RETURN(false): fi: if nops(MC)<>4 then print(`The input should be a 4-list`): RETURN(false): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: if not type(LL,set) then print(LL,`should be a set`): RETURN(false): fi: if not type(RL,set) then print(RL,`should be a set`): RETURN(false): fi: if not type(Nei,list) then print(Nei, `should be a list`): fi: if not type(Wts,list) then print(`The fourth item of the input-list should be a list`): RETURN(false): fi: N:=nops(Nei): kv:={seq(i,i=1..N)}: if LL minus kv<>{} then print(LL, `should be a subset of`,kv): RETURN(false): fi: if RL minus kv<>{} then print(RL, `should be a subset of`,kv): RETURN(false): fi: for i from 1 to nops(Nei) do if not type(Nei[i],set) then print(`The `, i, `-th item of the third item should be a set`): RETURN(false): fi: for i1 from 1 to nops(Nei[i]) do if not (type(Nei[i][i1],list) and nops(Nei[i][i1])=2 and type(Nei[i][i1][2],integer) and Nei[i][i1][2]>0 ) then print(Nei[i][i1], `should be a pair of inegers`): RETURN(false): fi: od: lu:={seq(Nei[i][i1][1],i1=1..nops(Nei[i]))}: if lu minus kv<>{} then print(`The `, i, `-th item of the third item should be a multi-subset of`): print(kv): RETURN(false): fi: od: if not type(Wts,list) then print(`The fourth item of the input-list should be a list`): RETURN(false): fi: if nops(Wts)<>N then print(`The fourth (and last) item in the input-list should be`): print(`of the same length as the third item`): RETURN(false): fi: for i from 1 to nops(Wts) do if not (type(Wts[i],integer) and Wts[i]>0) then print(`The `, i, `-th entry in the 4th item of the input list`, Wts[i]): print(`should be a positive integer `): RETURN(false): fi: od: true: end: #SolveMC2(MC,s): The generating function for all paths #on the Markov-Chain of type I, MC, in the variable s #see ezra(SolveMC1) for more details SolveMC2:=proc(MC,s) local eq,var,i,LL,RL,Nei,Wts,N,eq1,A,lu,j,Sakh,mu: if not KosherMC2(MC) then ERROR(`The first argument should be a type-II Combinatorial Markov Chain`): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): eq:={}: var:={}: for i from 1 to N do var:=var union {A[i]}: if member(i,RL) then eq1:=A[i]-s^Wts[i]: else eq1:=A[i]: fi: lu:=0: Sakh:=Nei[i]: for j from 1 to nops(Sakh) do lu:=lu+Sakh[j][2]*A[Sakh[j][1]]: od: eq1:=eq1-s^Wts[i]*lu: eq:=eq union {eq1}: od: var:=solve(eq,var): mu:=0: for i from 1 to nops(LL) do mu:=mu+subs(var,A[LL[i]]): od: normal(mu): end: #SolveMC2series(MC,L): The lists whose i^th term #is the coefficient of s^i in SolveMC2(MC,s) SolveMC2series:=proc(MC,L) local LL,RL,Nei,Wts,N,MW,A,TOT,cur,Sakh,i,j,k,tot,sa: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): MW:=max(op(Wts)): TOT:=[]: for i from 1 to N do A[i]:=[seq(0,j=1..MW)]: od: for j from 1 to L do for i from 1 to N do if member(i,RL) and Wts[i]=j then cur[i]:=1: else cur[i]:=0: fi: Sakh:=Nei[i]: for k from 1 to nops(Sakh) do sa:=Sakh[k]: cur[i]:=cur[i]+sa[2]*A[sa[1]][MW-Wts[i]+1]: od: od: tot:=0: for i from 1 to nops(LL) do tot:=tot+cur[LL[i]]: od: TOT:=[op(TOT),tot]: for i from 1 to N do A[i]:=[op(2..MW,A[i]),cur[i]]: od: od: TOT: end: #SolveMC2seriesS(MC,L,s): The first L terms in the sequence #weight-enumerating the number of words of weight n (or t^n) #(depending on your def. of weight) in the Markov #Chain [LeftLetters,RightLetters,NeighborLists,WtList] #that start in one of the left-letters and ends in #one of the right-letters #according to the weight: number of letters SolveMC2seriesS:=proc(MC,L,s) local LL,RL,Nei,Wts,N,MW,A,TOT,cur,Sakh,i,j,k,tot,sa: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]:Wts:=MC[4]: N:=nops(Wts): MW:=max(op(Wts)): TOT:=[]: for i from 1 to N do A[i]:=[seq(0,j=1..MW)]: od: for j from 1 to L do for i from 1 to N do if member(i,RL) and Wts[i]=j then cur[i]:=s: else cur[i]:=0: fi: Sakh:=Nei[i]: for k from 1 to nops(Sakh) do sa:=Sakh[k]: cur[i]:=expand(cur[i]+sa[2]*s*A[sa[1]][MW-Wts[i]+1]): od: od: tot:=0: for i from 1 to nops(LL) do tot:=tot+cur[LL[i]]: od: TOT:=[op(TOT),tot]: for i from 1 to N do A[i]:=[op(2..MW,A[i]),cur[i]]: od: od: TOT: end: #####END SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE II #####BEGIN SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE III #KosherMC3(MC): checks whether MC is (the profile) of #type III (a Vertex-Weighted Non-Simple Combinatorial Markov Chain) KosherMC3:=proc(MC) local LL,RL,Nei,N,i,kv,lu,i1: if not type (MC,list) then print(`The input should be a list`): RETURN(false): fi: if nops(MC)<>3 then print(`The input should be a 3-list`): RETURN(false): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]: if not type(LL,set) then print(LL,`should be a set`): RETURN(false): fi: if not type(RL,set) then print(RL,`should be a set`): RETURN(false): fi: if not type(Nei,list) then print(Nei, `should be a list`): fi: N:=nops(Nei): kv:={seq(i,i=1..N)}: if LL minus kv<>{} then print(LL, `should be a subset of`,kv): RETURN(false): fi: if RL minus kv<>{} then print(RL, `should be a subset of`,kv): RETURN(false): fi: for i from 1 to nops(Nei) do if not type(Nei[i],set) then print(`The `, i, `-th item of the third item should be a set`): RETURN(false): fi: for i1 from 1 to nops(Nei[i]) do if not (type(Nei[i][i1],list) and nops(Nei[i][i1])=2 and type(Nei[i][i1][2],integer) and Nei[i][i1][2]>0 ) then print(Nei[i][i1], `should be a pair of inegers`): RETURN(false): fi: od: lu:={seq(Nei[i][i1][1],i1=1..nops(Nei[i]))}: if lu minus kv<>{} then print(`The `, i, `-th item of the third item should be a subset of`): print(kv): RETURN(false): fi: od: true: end: #SolveMC3(MC,t): Given a variable t, and #the profile of a type-III #(Edge-Weighted, with no multiple edges) #Combinatorial Markov Chain [LeftLetters,RightLetters, #TransMatrx], finds the sum of the weights of all words that #start with a letter of LeftLetters and ends with a letter #of RightLetters, as a generating function in the variable t # SolveMC3:=proc(MC,t) local eq,var,a,gu,LL1,RL1,TM,eq1,lu,i,j: if not KosherMC3(MC) then ERROR(`The first argument should be a type-III Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: eq:={}: var:={}: for i from 1 to nops(TM) do var:=var union {a[i]}: if member(i,RL1) then eq1:=a[i]-1: else eq1:=a[i]: fi: lu:=TM[i]: for j from 1 to nops(lu) do eq1:=eq1-a[lu[j][1]]*t^lu[j][2]: od: eq:=eq union {eq1}: od: var:=solve(eq,var): if var=NULL then RETURN(0): fi: gu:=0: for i from 1 to nops(LL1) do gu:=normal(gu+subs(var,a[LL1[i]])): od: gu: end: #SolveMC3series(MC,M): Given a Markov Chain finds the sequence #whose i^th member is the number of paths of weight i #for 0<=i<=M SolveMC3series:=proc(MC,M) local a,i,SID,gu,gadol,LL1,RL1,TM,mispar,j,lu,i1,m,mu,sakhen,kha: if not ( type(M,integer) and M>=0 ) then ERROR(`The second argument must be a positive integer `): fi: if not KosherMC3(MC) then ERROR(`The first argument should be a type-III Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: mispar:=nops(TM): gu:={}: for i from 1 to mispar do lu:=TM[i]: for j from 1 to nops(lu) do gu:=gu union {lu[j][2]}: od: od: gadol:=max(op(gu)): for i from 1 to mispar do if member(i,RL1) then a[i]:=[seq(0,i1=1..gadol-1),1]: else a[i]:=[seq(0,i1=1..gadol)]: fi: od: SID:=[]: for m from 1 to M do for i from 1 to mispar do mu:=TM[i]: lu:=0: for j from 1 to nops(mu) do sakhen:=a[mu[j][1]]: lu:=lu+sakhen[nops(sakhen)-mu[j][2]+1]: od: kha[i]:=lu: od: gu:=0: for i from 1 to nops(LL1) do gu:=gu+kha[LL1[i]]: od: SID:=[op(SID),gu]: for i from 1 to mispar do a[i]:=[op(2..nops(a[i]),a[i]),kha[i]]: od: od: SID: end: #SolveMC3seriesS(MC,L,s): Given a Markov Chain finds the sequence #whose i^th member is the generating function of paths of weight i #with weight s^(length) #for 0<=i<=M SolveMC3seriesS:=proc(MC,L,s) local a,i,SID,gu,gadol,LL1,RL1,TM,mispar,j,lu,i1,m,mu,sakhen,kha: if not ( type(L,integer) and L>=0 ) then ERROR(`The second argument must be a positive integer `): fi: if not KosherMC3(MC) then ERROR(`The first argument should be a type-III Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: mispar:=nops(TM): gu:={}: for i from 1 to mispar do lu:=TM[i]: for j from 1 to nops(lu) do gu:=gu union {lu[j][2]}: od: od: gadol:=max(op(gu)): for i from 1 to mispar do if member(i,RL1) then a[i]:=[seq(0,i1=1..gadol-1),1]: else a[i]:=[seq(0,i1=1..gadol)]: fi: od: SID:=[]: for m from 1 to L do for i from 1 to mispar do mu:=TM[i]: lu:=0: for j from 1 to nops(mu) do sakhen:=a[mu[j][1]]: lu:=expand(lu+s*sakhen[nops(sakhen)-mu[j][2]+1]): od: kha[i]:=lu: od: gu:=0: for i from 1 to nops(LL1) do gu:=gu+kha[LL1[i]]: od: SID:=[op(SID),gu]: for i from 1 to mispar do a[i]:=[op(2..nops(a[i]),a[i]),kha[i]]: od: od: SID: end: #############END SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE III #############SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE IV ##(Edge-Weighted, using the profile) #KosherMC4(MC,t): checks whether MC is (the profile) of #type IV (an Edge-Weighted Combinatorial Markov Chain) KosherMC4:=proc(MC,t) local LL,RL,Nei,N,i,kv,lu,i1: if not type(t,string) then print(`The second argument should be a string`): RETURN(false): fi: if not type (MC,list) then print(`The input should be a list`): RETURN(false): fi: if nops(MC)<>3 then print(`The input should be a 3-list`): RETURN(false): fi: LL:=MC[1]:RL:=MC[2]:Nei:=MC[3]: if not type(LL,set) then print(LL,`should be a set`): RETURN(false): fi: if not type(RL,set) then print(RL,`should be a set`): RETURN(false): fi: if not type(Nei,list) then print(Nei, `should be a list`): fi: N:=nops(Nei): kv:={seq(i,i=1..N)}: if LL minus kv<>{} then print(LL, `should be a subset of`,kv): RETURN(false): fi: if RL minus kv<>{} then print(RL, `should be a subset of`,kv): RETURN(false): fi: for i from 1 to nops(Nei) do if not type(Nei[i],set) then print(`The `, i, `-th item of the third item should be a set`): RETURN(false): fi: for i1 from 1 to nops(Nei[i]) do if not (type(Nei[i][i1],list) and nops(Nei[i][i1])=2) then print(Nei[i][i1], `should be a pair [integer, polynomial in t] `): RETURN(false): fi: od: lu:={seq(Nei[i][i1][1],i1=1..nops(Nei[i]))}: if lu minus kv<>{} then print(`The first componets of the `, i, `-th item of the third item `): print(` should be a subset of`): print(kv): RETURN(false): fi: od: true: end: #SolveMC4(MC,t): Given a Markov Chain [LeftLetters,RightLetters, #TransMatrix], # Let N:=nops(TransMatrix), the vertices are assumed to be labelled # by 1, ..., N # The second input is a variable t # and the first input, MC is list of length 3 # # The 3 components of MC are as follows: # # LeftLetters is the set of vertices where a path may start # RightLetters is the set of vertices where a path may end # TransMatrix is a list of sets, where TransMatrix[i] is the # set consisting of pairs [j, polyn], where the coeff. of # of t^k in polyn is the number of edges from i to j with weight # k # #The output is the formal power series (necessarily a rational # function) whose coeff. of t^i is # the number of paths of weight i, that #start with a vertex of LeftLetters and ends with a vertex #of RightLetters, # SolveMC4:=proc(MC,t) local eq,var,a,gu,LL1,RL1,TM,eq1,lu,i,j: if not KosherMC4(MC,t) then ERROR(`The first argument should be a type-IV Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: eq:={}: var:={}: for i from 1 to nops(TM) do var:=var union {a[i]}: if member(i,RL1) then eq1:=a[i]-1: else eq1:=a[i]: fi: lu:=TM[i]: for j from 1 to nops(lu) do eq1:=eq1-a[lu[j][1]]*lu[j][2]: od: eq:=eq union {eq1}: od: var:=solve(eq,var): if var=NULL then RETURN(0): fi: gu:=0: for i from 1 to nops(LL1) do gu:=normal(gu+subs(var,a[LL1[i]])): od: gu: end: #SolveMC4series(MC,t,M): The list of length M whose i^th term #is the coefficient of t^i in SolveMC4(MC,t) SolveMC4series:=proc(MC,t,M) local a,i,SID,gu,gadol,LL1,RL1,TM,mispar,j,lu,i1,m,mu,sakhen,kha,lu1,j1: if not KosherMC4(MC,t) then ERROR(`The first argument should be a type-IV Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: mispar:=nops(TM): gu:={}: for i from 1 to mispar do lu:=TM[i]: for j from 1 to nops(lu) do gu:=gu union {degree(lu[j][2],t)}: od: od: gadol:=max(op(gu)): for i from 1 to mispar do if member(i,RL1) then a[i]:=[seq(0,i1=1..gadol-1),1]: else a[i]:=[seq(0,i1=1..gadol)]: fi: od: SID:=[]: for m from 1 to M do for i from 1 to mispar do mu:=TM[i]: lu:=0: for j from 1 to nops(mu) do sakhen:=a[mu[j][1]]: lu1:=mu[j][2]: for j1 from 1 to degree(lu1,t) do lu:=lu+coeff(lu1,t,j1)*sakhen[nops(sakhen)-j1+1]: od: od: kha[i]:=lu: od: gu:=0: for i from 1 to nops(LL1) do gu:=gu+kha[LL1[i]]: od: SID:=[op(SID),gu]: for i from 1 to mispar do a[i]:=[op(2..nops(a[i]),a[i]),kha[i]]: od: od: SID: end: #SolveMC4seriesS(MC,t,M,s): The list of length M whose i^th term #is the weight-enumerator of paths of weight i in the type-IV #combinatorial Markov Chain according to the weight s^length SolveMC4seriesS:=proc(MC,t,M,s) local a,i,SID,gu,gadol,LL1,RL1,TM,mispar,j,lu,i1,m,mu,sakhen,kha,lu1,j1: if not KosherMC4(MC,t) then ERROR(`The first argument should be a type-IV Combinatorial Markov Chain`): fi: LL1:=MC[1]: RL1:=MC[2]: TM:=MC[3]: mispar:=nops(TM): gu:={}: for i from 1 to mispar do lu:=TM[i]: for j from 1 to nops(lu) do gu:=gu union {degree(lu[j][2],t)}: od: od: gadol:=max(op(gu)): for i from 1 to mispar do if member(i,RL1) then a[i]:=[seq(0,i1=1..gadol-1),1]: else a[i]:=[seq(0,i1=1..gadol)]: fi: od: SID:=[]: for m from 1 to M do for i from 1 to mispar do mu:=TM[i]: lu:=0: for j from 1 to nops(mu) do sakhen:=a[mu[j][1]]: lu1:=mu[j][2]: for j1 from 1 to degree(lu1,t) do lu:=expand(lu+s*coeff(lu1,t,j1)*sakhen[nops(sakhen)-j1+1]): od: od: kha[i]:=lu: od: gu:=0: for i from 1 to nops(LL1) do gu:=gu+kha[LL1[i]]: od: SID:=[op(SID),gu]: for i from 1 to mispar do a[i]:=[op(2..nops(a[i]),a[i]),kha[i]]: od: od: SID: end: #############END SECTION DEALING WITH COMBINATORIAL MARKOV CHAIN of TYPE IV