Math 640: EXPERIMENTAL MATHEMATICS Spring 2007 (Rutgers University) Webpage

http://sites.math.rutgers.edu/~zeilberg/math640_07.html

Last Update: June 15, 2007.

Description

Experimental Mathematics used to be considered an oxymoron, but the future of mathematics is in this direction. In addition to learning the philosophy and methodology of this budding field, students will become computer-algebra wizards, and that should be very helpful in whatever mathematical specialty they'll decide to do research in.

We will first learn Maple, and how to program in it. This semester the focus will be on Wilf-Zeilberger theory and the so-called Holonomic ansatz.

There are no prerequisites, and no previous programming knowledge is assumed. People with no Maple background will be tutored. The final projects for this class may lead to journal publications.


Pick a project
Do A Good Deed in the Service of Experimental Mathematics!

One of the greatest tools for Experimental Math is Neil Sloane's Amazing Sequence Database, maintained by Neil, who donates so much of his free time so that the whole mathematical world can benefit. You can help out by going to the recent additions, and editing any of the still unedited sequences. For more details E-mail Neil Sloane (njas at research dot att dot com).


Diary and Homework

Programs done on Jan. 18, class

Program done on Jan. 22

Homework for Jan. 22, due Jan. 25:

  1. Write a program that inputs a list and finds a period, if it exists or returns FAIL.
  2. Write a program that inputs a list L, and outputs two lists L1, and L2 such that L=L1L2L2L2... or returns FAIL

Program done on Jan. 25, 2007

Homework for Jan. 25, due Jan. 29:

  1. Write a Maple program that inputs a finite list L and outputs the quadractic irrationality given by (L)^infinity (i.e. [op(L),op(L),op(L),op(L),op(L), ...].

    Hint: Let x= [op(L),op(L), op(L), ...]. Then x satisfies x=[op(L),x]. Use CFtoNu to evaluate [op(L),x] symolically, and use Maple's solve to find its positive root.

  2. Write a Maple program that inputs two finite lists S, and L and outputs the quadractic irrationality given by S(L)^infinity (i.e. [op(S), op(L),op(L),op(L),op(L),op(L), ...].

    Hint: Let y= [op(S),op(L),op(L), op(L), ...]. Then y satisfies y=[op(S),x]. Use CFtoNu and the previous program.

  3. Write a program that inputs a positive integer n. If it is a perfect square, it returns FAIL. If it is not, it first conjectures an infinite continued-fraction expansion for sqrt(n) of the form L1(L2)*, and then proceeds to prove it rigorously.

Programs done on Jan. 29, 2007

Homework for Jan. 29, due Feb. 1

  1. Finish the procedure GuessPol(L,x) in POL (version of Jan. 29),
  2. Write a procedure GuessRat(L,x,d1,d2) that inputs a list of numbers (or symbols) L, a variable x, and non-negative integers d1 and d2, and outputs a rational function R(x)=P(x)/Q(x), with the degree of P and Q being d1 and d2 respectively, such that R(i)=L[i] for i from 1 to nops(L) .

Programs done on Feb. 1, 2007

Homework for Feb. 1, due Feb. 5

  1. Extend procedure COV in brute (version of Feb. 1, 2007), to program the function gCov(S,L,r), where S is a set, L is a list of functions defined on S, and r is a list of non-negative integers, that computes the average of (L[1]-average(L[1])^r[1]*(L[2]-average(L[2])^r[2] .. . Use it to conjecture polynomial expressions for gCov(permute(n),[inv],[2]), gCov(permute(n),[maj],[2]), gCov(permute(n),[inv, maj],[2,2]).
  2. Use RAT to write a program that inputs a product of powers of binomial coefficients, F, and decides whether a(n):=sum(F(n,k),k=-n..n) is "nice", i.e. whether a(n+1)/a(n) is a rational function. Apply it to F=binomial(2*n,n+k), F=binomial(2*n,n+k)^3, F=(-1)^k*binomial(2*n,n+k)^3.

Programs done on Feb. 5, 2007

Homework for Feb. 5, due Feb. 8

  1. Finish up procedure Gnji(n,j,i,q) in PermStat, that is currently empty.
  2. Write a procedure for the analog of Fn(n,q) and Gn(n,q), call it Hn(n,t), for the generating function according to des (the number of descents)
  3. Write a procedure for the joint-weight-enumerator (alias generating function) for inv,maj, and des, let's call it FGHn(n,q1,q2,t) that is the sum of the weights of all permutations of {1, ..., n} where the weight of pi is q1^(inv(pi))*q2^(maj(pi))*t^(des(pi))
  4. Write a brute-force program for the above, and compare it for n up to 7.

Programs done on Feb. 8, 2007

Homework for Feb. 8, due Feb. 15

  1. Adapt procedures Moment(F,x,i) (added by me after class) that compute the moments-about-the-mean respectively, given in PermStat, to write a procedure gCovariance1 and qCovariance that inputs a function F of several variables, given in the list of variables x, and i is now a list of integers, to find what in file PermStat, to write a procedure qCovariance that does via generating functions what gCov does in brute.
  2. Use GuessPol of POL to conjecture polynomial expressions for the generalized covariance of maj and min E((maj-E[maj])^r (inv-E[inv)^s) for 1<=r,s<=5.
  3. Guess an expression for the Kurtosis of inv. (The Kurtosis is the fourth moment divided by the square of the second moment). What is its asymptotics as n goes to infinity?

Programs done on Feb. 12, 2007 (guest lecturer: Eric Rowland)

Program done on Feb. 15, 2007

Homework for Feb. 15, 2007, due Feb. 19

  1. Using mPOL, write a program, call it Celine1(F,n,k,N,K,d), that inputs an expression F that depends on n and k, symbols n, and k, and symbols N and K that denote the shift operators in n and k respectively: (i.e. NF(n,k):=F(n+1,k), KF(n,k):=F(n,k+1)), and outputs a conjectured recurrence operator P(N,K,n), of degree d in all N,K,n, that annihilates F(n,k), or FAIL, if it fails.

    For example, Celine1((n+k)!/n!/k!,n,k,N,K,1); should return NK-K-N .

  2. By using Celine1 for d=1, 2, .., Deg, write a program, call it Celine(F,n,k,N,K,Deg), that inputs an expression F that depends on n and k, symbols n, and k, and symbols N and K that denote the shift operators in n and k respectively: (i.e. NF(n,k):=F(n+1,k), KF(n,k):=F(n,k+1)), and a positive integer d, and outputs a conjectured recurrence operator P(N,K,n), of degree<= Deg in all N,K,n, that annihilates F(n,k), or FAIL, if it fails.

    Program done on Feb. 19, 2007

    • Celine.txt (version of Feb. 19, 2007), a Maple program that inputs an expression F in two discrete variables n and k, and positive integers degn, degtN, degK, and outputs, if possible a linear recurrence operator P(N,K,n) annihilating F.

    Homework for Feb. 19, 2007, due Feb. 26

    1. Using Celine1 as a subroutine, write a program, call it Celine2(F,n,k,N,K,degN,maxC) that inputs an expression F in n and k, and finds a linear recurrence operator P(N,K,n) annihilating F of order <=degN in n and with degK+degn<=maxC .
    2. Using Celine2 as a subroutine, write a program, call it Celine(F,n,k,N,K,maxC) that finds a linear recurrence operator P(N,K,n) annihilating F, of smallest possible order with degK+degn<=maxC .
    3. Write a procedure, Sumk(F,n,k,L), that inputs F, an expression in n and k that is known to be 0 for k sufficiently large and sufficiently small, and a positive integer L, and outputs the first L terms of the sequence a(n):=sum(F(n,k),k=-infinity..infinity);

    4. Write a procedure that verifies that if P(N,K,N) is the output of Celine, then the operator P(N,1,n) annihilates the sequence outputted by Sumk(F,n,k,L) .

    Maple worksheet done on Feb. 22, 2007 (Guest Lecturer: Lara Pudwell)

    Lara talked about using Maple in Calculus. See

    Program done on Feb. 26, 2007

    • Celine.txt (version of Feb. 26, 2007), a Maple program that inputs an expression F in two discrete variables n and k, and a positive integer A, and outputs, if possible a linear recurrence operator P(N,K,n) annihilating F with the sum of all the degrees <=A .

    Homework for Feb. 26, 2007, due March 1, 2007

    1. Write the program CelineWZ that is currently empty in: Celine.txt (version of Feb. 26, 2007).
    2. Extend Celine to find operators P(N,n,K1,K2) annihilating expressions F in (n,k1,k2) . Try it out on n!/k1!/k2!/(n-k1-k2)!, and (n!/k1!/k2!/(n-k1-k2)!)^2 .

    Program done on March 1, 2007

    • Celine.txt (version of March 1, 2007), a Maple program that inputs an expression F in two discrete variables n and k, and a positive integer A, and outputs, if possible a linear recurrence operator P(N,K,n) annihilating F with the sum of all the degrees <=A .

    Homework for March 1, 2007, Due March 5, 2007

    1. (repeat of the one above, since no one did it) Extend Celine to find operators P(N,n,K1,K2) annihilating expressions F in (n,k1,k2) . Try it out on n!/k1!/k2!/(n-k1-k2)!, and (n!/k1!/k2!/(n-k1-k2)!)^2 .
    2. Write CelineWZverbose that inputs the same as Celine, but finds the linear recurrence satisfied by a(n):=sum(F(n,k),k) and outputs a stupid-human readable proof.
    3. Write a symbolic version of Celine, that looks for an operator P(n,K,N) viewed as a member of C[n](K,N) that annihilates F(n,k) using the fact that N^i*K^j F(n,k)/F(n,k)=F(n+i,k+j)/F(n,k) is a rational function of (n,k) that can be viewed as a rational function of k with coefficients in C[n]. (Hint: use ApplyOperS).
    4. Look at Folkmar Bornemann's 2-line code for solving Don Knuth's Monthly problem, and compute S(m,m). Do you get the right answer? (Extra credit: can you explain why?)

    Program done on March 5, 2007

    Homework for March 5, 2007, Due March 8, 2007

    1. Use procedure SeqToCfinite1(L,n) of Cfinite.txt, to write procedure SeqToCfinite(L) that finds a linear recurrence equation with constant coefficients of order <=(nops(L)-4)/2, of lowest possible order, followed by the list of initial conditions (of the same length).
    2. Write a procedure CfiniteToSeq(R,N), that inputs a a pair [rec,ini], where rec represents a linear recurrence equation with constant coefficients (in our notation), and ini the initial conditions (starting at 1), and also inputs a positive integer N, and outputs the first N terms of the sequence obeying the recurrence rec under the initial conditions given by ini.
    3. Write a "C-finite" calclulator. Write Add1(R1,R2) and Mul1(R1,R2), where R1=[rec1,ini1], R2=[rec2,ini2]. Do it completely empirically, by using SeqToCfinite and CfiniteToSeq. Figure out the necessary number of terms needed.
    4. Write a program that inputs R=[rec,ini] and outputs a non-zero polynomial P such that P(a(n),a(n+1))=0 for all n, where a(n) is the sequence defined by R, or else returns FAIL.

    Program done on March 8, 2007

    Homework for March 8, 2007, Due March 19, 2007

    1. Use procedure MulC to write a procedure PowC(C,r) that inputs a C-finite sequence C=[C1,C2] and a non-negative integer r, and outputs the C-finite representation for its r-th power.
    2. If you haven't written the program, asked for the last time's homework, that inputs R=[rec,ini] and outputs a polynomial P such that P(a(n),a(n+1))=0 for all n, do it now. Use the C-finite calculator that we have develped to prove and any such identity rigorously. Do it by calculating the a priori order of the recurrence satisfied by b(n):=P(a(n),a(n+1)) using the fact that the order of a sum is the sum of the orders and the order of a product is the product of the orders, and then checking the initial conditions accordingly.
    3. (challenge) A sequence is called P-finite if it satisfies a linear recurrence equation with polynomial coefficients:

      p_0(n)a(n)+p_1(n) a(n-1)+ ... + p_L(n)a(n-L)=0

      for some positive integer L (the order) and polynomials p_0(n), ..., p_L(n). Write a program Pfinite.txt, that does the analog for P-finite sequences what Cfinite.txt does for C-finite sequences.

    4. Use the procedure SeqToPfinite that you did above, to write a procedure that inputs a hypergeometric bi-sequence F(n,k) (product of binomial coefficinets, for example binomail(n,k)^2*binomial(n+k,k)^2) and outputs a guessed linear recurrence equation with polynomial coefficients satisfied by a(n)=Sum(F(n,k),k=0..n) .

    Program done on March 19, 2007

    Homework for March 19, 2007, Due March 26, 2007

    [Corrected and Modified (thanks to Ke Wang), March 22, 2007]
    1. Write an analog of GenPol(varL,degL,a,s0) of mPOL.txt, Let's call it GP(n,K,M,X,a,s0). It inputs a pos. integer n, a pos. integer K, an integer M, a symbol X, a symbol a, and a pos. integer s0, and outputs a generic polynomial in X[1],X[2], .., X[n], where the degree in each variable is between -K and K and is homogeneous of degree M (in other words, each monomial has the form X[1]^a1*...*X[n]^an, where max(|a1|, ..., |ak|)<=K and a1+...+ak=M , with coeffs. {a[s0],a[s0+1], ...} , followed by the set of coefficients.
    2. Use the above, to write a program JB(Li,k,K,M,X), that tries to conjecture relations P(F(n),F(n+1), . . , P(n+k-1))=0 where P is a polynomial as above.
    3. Using the C-finite calculator we programmed in CfiniteOccam.txt, write a program that rigorously proves the conjectures found in the previous program.
    4. Reminder: the class of Thurs. March 22, 2007 will be at Hill 705 (just this time).

    March 22, 2007

    We all attended the fascinating talk by Prof. Tewodros Amdeberhan, of Tulane University about the dynamics of the arctan function.

    Program done on March 26, 2007

    Homework for March 26, 2007, Due March 29, 2007

    1. Define a generalized r-Gelfand Pattern to have the same conditions as a Gelfand pattern (i.e. that the entry in the space between two consecutive entries in a given row is weakly between them) and that the difference between two consecutive entries is great or equal to r (i.e. if the entries in a row are a1, a2, ..., an, then a2-a1>=r, a3-a2>=r, ..., an-a_{n-1}>=r. a 0-Gelfand pattern is a Gelfand pattern. Modify procedures Children(a) and G(a) to Children1(a,r) and G(a,r) that do the analogous thing for generalized r-Gelfand patterns.
    2. Conjecture a closed form formula for G1([1, ..., n],1)
    3. Conjecture a closed form formula for G1([1, 3, 5..., 2*n-1],1)
    4. (5 dollars) Prove the conjectured formula for G([a1, ..., an]) that we found in class
    5. [corrected thanks to Justin P.] A plane partition is an m by n matrix whose entries are nonnegative integers, and that is weakly decreasing along both rows and columns. Let F(m;[a1, ..., an]) be the number of plane partitions with n-rows and m columns, whose leftmost column is (a1, ..., an). Write a program to compute F(m;[a]). Use it to conjecture a closed-form formula for F(m;[k$n]);
    6. Extend the C-finite calculator we programmed in CfiniteOccam.txt to write a procedure that inputs a C-finite sequence a(n) (in the Occam data structre), and two positive integers A and B, and outputs the new sequence sum(binomial(A*n,i)*a(B*i),i=0..A*n). (Hint: by general nonsense, this new sequence has the same order as a(n)).

    Program done on March 29, 2007

    Homework for March 29, 2007, Due April 2, 2007

    1. Read and understand Recitation II of Three Recications on Holonomic Functions and Hypergeometric Series.
    2. In class, when we programmed Gosper(a,n), in the file gosper.txt, we cut two corners. Eliminate them both. (The first one is to change infinity=1000 back to infinity=infinity, using the resultant, and the second one is to find a sharp upper bound for the degree of f(n) by writing f(n)=a[d]*n^d+a[d-1]*n^(d-1) + ... for symbolic d, pluging into the Gosper equation (*), and solving for d, and seeing whether you get a non-negative integer (usually you don't but when it does happen, I call it a miracle).
    3. Write a program TestGosper(S,n), that inputs an arbitrary hypergeomertric equence S(n), computes a:=S-subs(n=n-1,S), simplifies a(n) as much as possible, then applies Gosper(a,n) and verifies that it is indeed S. It returns true or false.
    4. Write a program RandomHyper(d1,d2,K,n) that inputs positive integers d1, d2, K, and a symbol n, and outputs a random hypergeometric sequence of the form (a[1]*n+b[1])!*...*(a[d]*n+b[d])!*P(n), where a[1], ..., a[d], b[1], ..., b[d] are random integers between -K and K and P is a random polynomial of n of degree d2 with coeffs. that are random integers between -K and K. (Hint: use maple's rand. Recall that to define a fair die of 2*K+1 faces you do ra:=rand(-K..K), and than ra() gives you a (pseudo) random integer in [-K..K]).
    5. Interface TestGosper and RandHyper in order to test Gosper(a,n) for 1000 different random inputs.

    Program done on April 2, 2007

    Homework for April 2, 2007, Due April 5, 2007

    1. Read and understand gosper.txt. Sorry for messing up in class.
    2. Write an extension of Gosper(p0,a,n), call it, GosperWP(p0,a,n,para) in the file gosper.txt, that inputs a polynomial p0 that depends (linearly) on parameters in a set para, and outputs a specialization of the set of parameters para, that makes p0(n)*a(n) be gosperable (i.e. makes it such that there exists a hypergeometric S(n) such that p0(n)*a(n)=S(n)-S(n-1) The output should be the "solution set" of para, followed by S. For example GosperWP(n+a1,(n-1)!,n,{a1}); should return {a1=-1},n! .

    Program done on April 5, 2007

    Homework for April 5, 2007, Due April 9, 2007

    1. ($10 for the first solution) Debug Gosper(a,p,n) in gosper.txt, so that it will work well with WZ(F,a,k,n) in WZ.txt, with the inputs WZ(binomial(n,k)^2,binomial(2*n,n),k,n); and WZ((-1)^k*binomial(2*n,n+k)^3,(3*n)!/n!^3,k,n);
    2. A Generalized k-Somos-sequence , a(n)=a(n,c[1], ..., c[k-1]) is defined by a(n)*a(n-k)=c[1]*a(n-1)*a(n-k+1)+c[2]*a(n-2)*a(n-k+2)+...+c[k-1]*a(n-k+1)*a(n-1). Write a program to generate the first L terms of a such a generalized Somos sequence. With all the c[i]'s equal to 1, discover empirically for which k you get always integers. For k=4, k=5, k=6 discover other choices of c's that give you integers.

      Program done on April 9, 2007

      Homework for April 9, 2007, Due April 12, 2007

      1. Finish WZv(F,a,n,k,Author); that you started in class, for a verbose statement and proof of a WZ-style proof of an explicitly evaluable binomial coefficient identity.
      2. Write a program Zv(F,n,k,Author); that inputs a hyergeometric sequence F of (n,k), symbols n and k, and outputs a paper that states and proves a linear recurrence equation with polynomial coefficients satisfies by a(n):=Sum(F(n,k),k=-infinity..infinity).
      3. Right now, in Z(F,n,k,N), you have an annoying constant, since this is a homogeneous equation. Modify Z(F,n,k,N) to get rid of that annoying constant.
      4. Look Z(binomial(n,k)^r,n,k,N)[1] for r between 1 and 8. Can you make conjectures about the order (as a function of r)?, about the degree of the coefficients?

        Program done on April 12, 2007

        Homework for April 12, 2007, Due April 16, 2007

        1. Modify program SeqFromRec(ope,n,N,Ini,L) in WZ.txt to write a program TermFromRec(ope,n,N,Ini,L) that inputs the same thing as before, but outputs ONLY the L-th term. Make it as memory-efficient as possible. With ope:=Z(binomial(n,k)^2*binomial(n+k,k)^2,n,k,N,10)[1]; and Ini1:=[1,5], Ini2:=[0,6], find the best rational approximation to Zeta(3), that you can come up with.
        2. Do analogous things for
          ope:=Z(binomial(n,k)^2*binomial(n+k,k),n,k,N,10)[1]; and Zeta(2) (decide the appropriate Ini1 and Ini2 that will make it work) and
          ope:=Z(binomial(n,k)*binomial(n+k,k),n,k,N,10)[1]; and ln(2) (decide the appropriate Ini1 and Ini2 that will make it work).
        3. Following the article The Method of Differentiating Under the Integral Sign by Gert Almkvist and Dr. Z., program the continuous analog of Gosper's algorithm in pp. 6-8.

          Program that would have been done on April 16, 2007

          • If you haven't done the continuous analog of Gosper, asked for in last time's homework, do so, right now. Call it AZ1(F,x), where F is an expression in x describing a hyperexponential function (i.e. F'(x)/F(x) is a rational function of x). It should return a hyperexponential expression G, in x, such that G'(x)=F(x) or FAIL.

          Homework for April 16, 2007, Due April 19, 2007

          1. Assuming that you did the continuous analog of Gosper asked for above, write AZ1WP(p,F,x,para), the analog of GosperWP.
          2. Using AZWP, write AZd(F,x,n,N), a program that implements the Almkvist-Zeilberger algorithm as described in the above mentioned paper The Method of Differentiating Under the Integral Sign, where F(x,n) is an expression such that both F'(x,n)/F(x,n) and F(x,n+1)/F(x,n) are rational functions of (x,n) and outputs a recurrence operator ope(n,N) , followed by a certificate G(x,n) such that
            ope(n,N)F(x,n)=diff(G(x,n),x)
          3. Using AZWP, write AZc(F,x,y,Dx), a program that implements the Almkvist-Zeilberger algorithm as described in the above mentioned paper The Method of Differentiating Under the Integral Sign, where F(x,y) is an expression such that both diff(F,x)/F and diff(F,y)/F are rational functions of (x,y) and outputs a linear differential operator with polynomial coefficients ope(x,Dx) , followed by a certificate G(x,y) such that
            ope(x,Dx)F(x,y)=diff(G(x,y),y)
          4. Test both AZd and AZc with the examples given in the paper and make some of your own.

            Program done on April 19, 2007

            Homework for April 19, 2007, Due April 23, 2007

            1. If you didn't finish the homework due today, or had trouble doing it, use the current version of AZ.txt to finish last time's assignment.
            2. Use AZd(F,x,n); to find a linear recurrence equation satisfied by a(n):= coeff. of x^0 in (x+1+1/x)^n.
            3. use AZc(F,x,y) to find a differential equation satisfied by int(exp(-x^2-y^2)*(x-y)^n,y=-..infinity..infinity);

            Program done on April 23, 2007

            Homework for April 23, 2007, Due April 26, 2007

            1. Write a program that does the Continuous analog of AZd(F,x,n,N), call it AZc(F,x,y,Dy). It inputs a hyperexponential function F of x and y (i.e. BOTH F_x/F and F_y/F are rational functions of x and y), and outputs a differential operator, ope(x,Dx), annihilating
              a(x):=int(F(x,y), y=-infinity..infinity);
              and the certificate.
            2. Test your AZc on the following:
              • F=1/(1-(x+1/x)*y) ,
              • F=1/(1-(x+1+1/x)*y) .
              • F=(x-y)^4*exp(-x^2-y^2) .
            3. Look up the Rodrigues-type formulas for the Hermite, Laguere, and Jacobi polynomials, and use AZd to derive a three-term recurrence equation.
            4. Look up the generating functions for the Legendre, Hermite, and Laguerre polynomials, and use AZd to derive recurrences for them.

              (Hint: if a sequence of polynomials Pn(x) has the generating function G(x,t)=Sum(Pn(x)*t^n,n=0..infinity), then Pn(x) is the contour integral (up to a const. multiple), w.r.t. t, of G(x,t)/t^(n+1)).

              Program done on April 26, 2007

              Homework for April 26, 2007, Due April 30, 2007

              1. A sequence a(n) is q-hypergeometric if R(n):=a(n)/a(n-1) is a rational function of q^n (and q). Design a q-analog of Gosper's algorithm. Describe the sequence a(n) not explicitly but in terms of the rational function R(q^n,q). The program should output another rational function R'(n) such that the q-hypergeom. sequence s(n) defined by s(n)/s(n-1)=R'(n) satisfies s(n)-s(n-1)=a(n), if it exists, or returns FAIL.

              What we did on the (last!) class of April 30, 2007

              It was a beautiful day, and the computer room was unbearable, so we went outside and worked on the beginning of a software development project that the whole class would participate in. It is to create and solve KAKURU puzzles.

              Lara is the boss. Eric, Baxter, and Aek are the sub-bosses. Aek's team consists of Ke, Humberto and Mangesh. Eric's team consists of Justin, Mike, and Emilie. Baxter's team consists of Paul and Jason. I hope to post a working Maple program next Monday.

              KAKURO: The Whole Class's Group effort!


              This ends this semester. Have a great summer! I will post the students' final projects below.

              FINAL PROJECTS

              Below are the students' final porjects.
              Dr. Z.'s teaching page