
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) ++ ")"

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

Sorry, I just assumed everyone has a copy of CLRS :) The following link
describes the problem and has the imperative pseudo-code of the solution.
http://www.columbia.edu/~cs2035/courses/csor4231.F09/matrix-chain.pdf
On Tue, Jul 6, 2010 at 3:53 PM, Tom Doris
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
wrote: 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

Ali Razavi wrote:
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.
Dynamic programming algorithms follow a common pattern: * Find a suitably small collection of subproblems that can be used to solve the original problem * Tabulate the solutions to the subproblems, also called *memoization* These are two separate concerns and, unlike the prototype imperative solutions, are best implemented separately. Thanks to lazy evaluation, memoization can be implemented very elegantly in Haskell. First, it should be a higher-order functions and second, you don't need to implement a particular order by which the memo table is filled, lazy evaluation will figure that out for you. You already know the latter trick, but here is another example: http://article.gmane.org/gmane.comp.lang.haskell.beginners/554 But it doesn't stop here: there are very systemic ways to tackle the first part of dynamic programming, i.e. to *derive* dynamic programming algorithms from just the problem specification! An example and further references are given here http://thread.gmane.org/gmane.comp.lang.haskell.cafe/42316/focus=42320 Concerning matrix chain multiplication, here is my implementation. Note the use of telling names and algebraic data types; there is no need to get lost in a maze of twisty little indexes, all alike. import Data.List import Data.Array import Data.Ord type Dimension = (Int,Int) type Cost = Int -- data type representing a parenthesization, -- caches cost to calculate and dimension of the result matrix data Parens = Mul !Cost Dimension Parens Parens | Matrix Dimension deriving (Show) -- retrieve cached vallues cost :: Parens -> Cost cost (Mul c _ _ _) = c cost (Matrix _) = 0 dimension :: Parens -> Dimension dimension (Mul _ d _ _) = d dimension (Matrix d) = d -- smart constructor mul :: Parens -> Parens -> Parens mul x y = Mul (cost x + cost y + n*m*p) (n,p) x y where (n,m,p) = (fst $ dimension x, snd $ dimension x, snd $ dimension y) -- dynamic programming algorithm solve :: [Int] -> Parens solve matrices = chain 1 n where n = length matrices - 1 dimensions = array (1,n) . zip [1..] $ zip (init matrices) (tail matrices) chain = memoize n chain' chain' i j | i == j = Matrix (dimensions ! i) | otherwise = best [mul (chain i k) (chain (k+1) j) | k <- [i..j-1] ] best = minimumBy (comparing cost) -- memoize a function on a "square" [1..n] x [1..n] memoize :: Int -> (Int -> Int -> a) -> (Int -> Int -> a) memoize n f = \i j -> table ! (i,j) where table = array ((1,1),(n,n)) $ [((i,j), f i j) | i <- [1..n], j <- [1..n]] Example output: *Main> cost $ solve [10,100,5,50,1] 1750 I didn't need to debug this code, because it's obviously correct. Put differently, instead of spending my effort on debugging, I have spent it on making the solution elegant. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Wednesday 07 July 2010 11:30:28, Heinrich Apfelmus wrote:
I didn't need to debug this code, because it's obviously correct. Put differently, instead of spending my effort on debugging, I have spent it on making the solution elegant.
Well done. Chapeau!
Regards, Heinrich Apfelmus

Daniel Fischer wrote:
Heinrich Apfelmus wrote:
I didn't need to debug this code, because it's obviously correct. Put differently, instead of spending my effort on debugging, I have spent it on making the solution elegant.
Well done. Chapeau!
:) Well, apart from the fact that the "obviousness" of this code also depends on the correctness of this particular division into subproblems, there is one piece of the code that is quite error-prone, namely the definition of chain and chain' : chain = memoize n chain' chain' i j | i == j = Matrix (dimensions ! i) | otherwise = best [mul (chain i k) (chain (k+1) j) | k <- [i..j-1] ] It is really easy to accidentally write chain' instead of chain and vice versa, leading to a black hole or a loss of memoization. (Using more distinct names doesn't necessarily help because there is almost no semantic difference between the two functions.) Trouble is that the type system won't catch such mistakes because the two functions have the same type. However, we can give chain and chain' different types by using the fixed point combinator and writing: chain = fix (memoize n . chain') chain' chain i j | i == j = Matrix (dimensions ! i) | otherwise = best [mul (chain i k) (chain (k+1) j) | k <- [i..j-1] ] Shadowing the variable chain in the definition of chain' is both intentional and harmless, since both variables chain will be bound to the very same function. In any case, chain' and chain now have different types and the burden of checking whether we've used them correctly is left to the compiler. (For those who don't know the fixed point combinator yet: I have recently made a short video about it: http://apfelmus.nfshost.com/blog/2010/07/02-fixed-points-video.html ) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Ali Razavi
-
Daniel Fischer
-
Heinrich Apfelmus
-
Tom Doris