
Is there an online version of the book, or failing that could you post the
full problem statement?
On 6 July 2010 17:45, Ali Razavi
In order to practice Haskell, I decided to program some algorithms from the CLRS book. Particularly, I tried to implement the Matrix Chain Order from Chapter 15 on Dynamic Programming. Here is my code. It seems to work, however, it looks ugly and it was a nightmare to debug. I appreciate comments about a more elegant solution, and generally the best way to implement these kinds of algorithms in Haskell. Style improvement suggestions are also welcome.
Best, Ali
import Data.Array
pp = [30,35,15,5,10,20,25]
para p = let n = length p - 1 msij = array ((1,1),(n,n)) ([((i,j), (0,0)) | i <-[1..n], j <-[1..n]] ++ [((i,j), (m, s))| l<-[2..n] , i<-[1..n-l+1] , let j = i + l - 1 , let qs = [q|k<-[i..j-1] , let q = fst (msij!(i,k)) + fst (msij!(k+1, j)) + p!!(i-1)*p!!k*p!!j] , let (m, s, c) = foldl (\(mz,sz,ind) x-> if x < mz then (x,ind,ind+1) else (mz,sz,ind+1)) (head qs, i, i) qs ]) in msij
chainSolve p = let sol = para p n = length p - 1 in do print $ fst $ sol!(1,n) putStrLn $ printSol sol 1 n "" where printSol s i j o = if i == j then o ++ "A" ++ (show i) else o ++ "(" ++ (printSol s i (snd (s!(i,j))) o) ++ (printSol s ((snd (s!(i,j)))+1) j o) ++ ")"
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners