Re: (Newbie) Dynamic Programming, Memoizing Etc.

Bryce Bockman wrote:
How would you guys memoize the following code.
simpleCalc :: (Int,Int) -> (Int,Int) simpleCalc (1,l) = (1,l+1) simpleCalc (x,l) | (odd x) = simpleCalc (((3*x) + 1), 1 + l) | otherwise = simpleCalc ((x `div` 2), 1 + l)
sCalc x = simpleCalc (x,0)
sCalcListRange a b = map sCalc [a..b]
sCalcListLengthRange a b = map snd (sCalcListRange a b)
The key is I need to calculate maximum (sCalcListLengthRange 1 1000000).
One observation is that `l' is merely `an iteration counter'. Therefore, the code can be simplified. The other observation is that memoizing all intermediate results may be expensive: the memoization table (a list, for example) will be big and sparsely populated. The cost of indexing in such a list can be significant. Here's a solution that seems to be balancing both costs. One can change the balance by modifying sc_upb.
module Foo where
import Data.Array
sc_upb = 100 sc = listArray (1,sc_upb) $ map sc_calc [1..]
sc_get i | i <= sc_upb = sc ! i sc_get i = sc_calc i
sc_calc :: Int -> (Int,Int) sc_calc 0 = (0,0) sc_calc 1 = (1,1) sc_calc x | odd x = let (r,c) = sc_get (3*x + 1) in (r, c+1) sc_calc x = let (r,c) = sc_get (x `div` 2) in (r, c+1)
sCalcListLengthRange' a b = map (snd . sc_calc) [a..b]
*Foo> maximum $ sCalcListLengthRange 1 10000 262 (1.57 secs, 82200088 bytes) *Foo> maximum $ sCalcListLengthRange' 1 10000 262 (1.18 secs, 61043084 bytes) there seems to be a benefit.
participants (1)
-
oleg@pobox.com