Difference between revisions of "Dynamic programming example"

From HaskellWiki
Jump to navigation Jump to search
m (Corrected bitmask of last example (0x8120 should be 0x80120))
(One intermediate revision by one other user not shown)
Line 28: Line 28:
 
buy n = r!n
 
buy n = r!n
 
where r = listArray (0,n) (Just (0,0,0) : map f [1..n])
 
where r = listArray (0,n) (Just (0,0,0) : map f [1..n])
f i = case (i>=6, r!(i-6))
+
f i = case attempt (i-6)
of (True, Just(x,y,z)) -> Just(x+1,y,z)
+
of Just(x,y,z) -> Just(x+1,y,z)
_ -> case (i>=9, r!(i-9))
+
_ -> case attempt (i-9)
of (True, Just(x,y,z)) -> Just(x,y+1,z)
+
of Just(x,y,z) -> Just(x,y+1,z)
_ -> case (i>=20, r!(i-20))
+
_ -> case attempt (i-20)
of (True, Just(x,y,z)) -> Just(x,y,z+1)
+
of Just(x,y,z) -> Just(x,y,z+1)
 
_ -> Nothing
 
_ -> Nothing
  +
attempt x = if x>=0 then r!x else Nothing
 
</haskell>
 
</haskell>
   
Line 92: Line 93:
 
iter 0 lst = odd lst
 
iter 0 lst = odd lst
 
iter n lst = iter (n-1) ((lst `shiftL` 1) .|.
 
iter n lst = iter (n-1) ((lst `shiftL` 1) .|.
if lst .&. 0x8120 /= 0 then 1 else 0)
+
if lst .&. 0x80120 /= 0 then 1 else 0)
 
</haskell>
 
</haskell>
   

Revision as of 19:44, 1 October 2011


Dynamic programming refers to translating a problem to be solved into a recurrence formula, and crunching this formula with the help of an array (or any suitable collection) to save useful intermediates and avoid redundant work.

Computationally, dynamic programming boils down to write once, share and read many times. This is exactly what lazy functional programming is for.

Sample problems and solutions

Available in 6-packs, 9-packs, 20-packs

A fast food place sells a finger food in only boxes of 6 pieces, boxes of 9 pieces, or boxes of 20 pieces. You can only buy zero or more such boxes. Therefore it is impossible to buy exactly 5 pieces, or exactly 7 pieces, etc. Can you buy exactly N pieces?

If I can buy i-6 pieces, or i-9 pieces, or i-20 pieces (provided these are not negative numbers), I can then buy i pieces (by adding a box of 6 or 9 or 20). Below, I set up the array r for exactly that, with r!0 forced to True to bootstrap the whole thing.

import Data.Array

buyable n = r!n
    where r = listArray (0,n) (True : map f [1..n])
          f i = i >= 6 && r!(i-6) || i >= 9 && r!(i-9) || i >= 20 && r!(i-20)

You certainly want to know how to buy N pieces, in addition to knowing whether it can be done. I now use the array to hold both kinds of information: r!i is Nothing if i pieces cannot be bought, or Just (x,y,z) if i pieces can be bought, and moreover it can be done by x boxes of 6, y boxes of 9, and z boxes of 20. Below the code for buy is more tedious (understandably) but is just a natural extension of the logic behind the code of buyable.

import Data.Array

buy n = r!n
    where r = listArray (0,n) (Just (0,0,0) : map f [1..n])
          f i = case attempt (i-6)
                of Just(x,y,z) -> Just(x+1,y,z)
                   _ -> case attempt (i-9)
                        of Just(x,y,z) -> Just(x,y+1,z)
                           _ -> case attempt (i-20)
                                of Just(x,y,z) -> Just(x,y,z+1)
                                   _ -> Nothing
          attempt x = if x>=0 then r!x else Nothing

Optional: If you know monads and that Maybe is a monad, you can write it in a more regular way:

import Data.Array
import Control.Monad(guard,mplus)

buy n = r!n
    where r = listArray (0,n) (Just (0,0,0) : map f [1..n])
          f i = do (x,y,z) <- attempt (i-6)
                   return (x+1,y,z)
                `mplus`
                do (x,y,z) <- attempt (i-9)
                   return (x,y+1,z)
                `mplus`
                do (x,y,z) <- attempt (i-20)
                   return (x,y,z+1)
          attempt x = guard (x>=0) >> r!x

This more regular code can be further generalized.

Optimization

Simple dynamic programing is usually fast enough (and as always, profile before optimizing!) However, when you need more speed, it is usually fairly easy to shave an order of magnitude off the space usage of dynamic programming problems (with concomitant speedups due to cache effects.) The trick is to manually schedule the computation in order to discard temporary results as soon as possible.

Notice that if we compute results in sequential order from 0 to the needed count, (in the example above) we will always have computed subproblems before the problems. Also, if we do it in this order we need not keep any value for longer than twenty values. So we can use the old fibonacci trick:

buyable n = iter n (True : replicate 19 False)
    where iter 0 lst = lst !! 0
          iter n lst = iter (n-1) ((lst !! 5 || lst !! 8 || lst !! 19) : take 19 lst)

At each call of iter, the n parameter contains (total - cur) and the lst parameter stores buyable for (cur-1, cur-2, cur-3, ...). Also note that the indexes change meaning through the cons, so we need to offset the !! indexes by 1.

We can improve this more by packing the bit array:

import Data.Bits

buyable n = iter n 1
    where iter :: Int -> Int -> Bool
          iter 0 lst = odd lst
          iter n lst = iter (n-1) ((lst `shiftL` 1) .|.
                                   if lst .&. 0x80120 /= 0 then 1 else 0)

This final version is compiled into a single allocation-free loop.