[Haskell-cafe] How to think about this? (profiling)

Patrick Perry patperry at stanford.edu
Tue Dec 16 18:11:06 EST 2008


I agree with everyone else who has said that the better solution is  
Lemmih's.  It is simple, fast, and does not use much memory.

On the other hand, here is a more faithful implementation of what you  
were trying to write.  To use mutable arrays, you need to work in  
either the IO or the ST monad.  The advantage of ST is the function  
"runST", which is roughly equivalent to "unsafePerformIO", but is much  
safer.

I hope this helps,


Patrick

\begin{code}

import Control.Monad
import Control.Monad.ST
import Data.Array.ST
import System.Environment

-- | Create an array for storing the results of foo 0 through foo n.
-- Initialize foo 0, foo 1, and foo 2, but set all other values to
-- 'missing'.
newMemo :: Int -> ST s (STUArray s Int Int)
newMemo n = do
     arr <- newArray (0,n) missing :: ST s (STUArray s Int Int)
     writeArray arr 0 0
     writeArray arr 1 1
     writeArray arr 2 2
     return arr

-- | Code to indicate a missing value in the memo array.
missing :: Int
missing = -1

-- | Compute the value of the function at @i@, using the memo-ed results
-- in the array.
fooWithMemo :: STUArray s Int Int -> Int -> ST s Int
fooWithMemo arr i = do
   x <- readArray arr i
   if x /= missing
       then return x
       else do
           r <- liftM3 (\ a b c -> a + b + c)
                    (fooWithMemo arr $ i - 1)
                    (fooWithMemo arr $ i - 2)
                    (fooWithMemo arr $ i - 3)
           writeArray arr i r
           return r

foo :: Int -> Int
foo n = runST $ do
     arr <- newMemo n
     fooWithMemo arr n

main = do
   (n:_)  <- liftM (map read) getArgs
   print $ foo n

\end{code}



More information about the Haskell-Cafe mailing list