
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