Hello everybody! For testing purposes, I punched down a small program which...
+ puts 2^n elements into an unmutable vector (fromList); + generates a random index in the vector (using random-mersenne); + reads the value at the index i and at i+{-2,-1,1,2} and makes product of these values (making sure the indices stay within the boundary of the vector using `mod 2^n'); + makes a new vector with the product replacing the element at the index; + repeats the whole process 10^7 times starting from the random index. Now, after enforcing a minimum of strictness and profiling the program, I find that for some odd reason the program spends most of its time calculating the product of the read numbers! This is completely contrary to what I expected; namely, that it would spend most of the time either a) generating random numbers, b) reading the vector, or c) making a new vector. But it turns out, that reading the vector or indeed making the new one takes only a fraction of the actual time. I have attached the program and the profile to this email. Could it be that profiling assigns the Cost Centres to the wrong parts of the program? Did I overlook something crucial? Most likely the program could be implemented in a smarter way, but it's pretty close to what my actual program looks like and it shows similar behaviour. (My code, additionally, has a Boltzmann-weighed probability condition on whether the new value gets written to the vector or not.) I would be very happy for some input on this, because I am pretty new to Haskell and I don't really know how to do proper profiling. Cheers Janis (This being my first email to this mailing list, I hope I adhere to all rules of conduct out there; please tell me if I should have written this email differently or more concise.)
{-# LANGUAGE BangPatterns #-} import qualified System.Random.Mersenne as R import qualified Data.Vector.Unboxed as V hiding ((!),(//)) import Data.Vector.Unboxed ((!),(//)) import Data.List import Control.Applicative lukUp :: V.Vector Int -> Int -> Int -> Int lukUp vs l i = let i' = i `mod` l in vs ! i' neighProd :: V.Vector Int -> Int -> Int -> Int neighProd vs l i = foldl' (\acc x -> acc * (lukUp vs l i) ) 1 [i-2 ,i-1 ,i ,i+1 ,i+2] randVec :: R.MTGen -> V.Vector Int -> Int -> IO (V.Vector Int) randVec rg vs l = do i <- (`mod` l) <$> R.random rg :: IO Int let !v' = neighProd vs l i vs' = vs // [(i,v')] return vs' iter :: R.MTGen -> V.Vector Int -> Int -> Int -> IO Int iter rg vs l n | n <= 0 = return $ V.foldl' (+) 0 vs | otherwise = do !vs' <- randVec rg vs l iter rg vs' l (n-1) main = do rg <- R.newMTGen Nothing let l = 64 vs = (V.fromList . take l . cycle) [1,-1] s <- iter rg vs l 10000000 print.show $ s
Tue Dec 11 14:47 2012 Time and Allocation Profiling Report (Final) vec +RTS -hy -p -RTS total time = 15.57 secs (15568 ticks @ 1000 us, 1 processor) total alloc = 11,520,059,680 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc neighProd Main 47.4 21.5 randVec.vs' Main 16.2 59.0 randVec Main 13.5 11.1 iter Main 9.5 5.6 lukUp.i' Main 4.2 1.4 lukUp Main 3.6 1.4 randVec.v' Main 3.2 0.0 neighProd.\ Main 2.3 0.0 individual inherited COST CENTRE MODULE no. entries %time %alloc %time %alloc MAIN MAIN 66 0 0.0 0.0 100.0 100.0 main Main 133 0 0.0 0.0 100.0 100.0 main.vs Main 137 1 0.0 0.0 0.0 0.0 iter Main 134 10000001 9.5 5.6 100.0 100.0 randVec Main 135 10000000 13.5 11.1 90.5 94.4 randVec.v' Main 140 10000000 3.2 0.0 60.8 24.3 neighProd Main 141 10000000 47.4 21.5 57.6 24.3 neighProd.\ Main 143 50000000 2.3 0.0 10.1 2.8 lukUp Main 144 0 3.6 1.4 7.8 2.8 lukUp.i' Main 145 10000000 4.2 1.4 4.2 1.4 lukUp Main 142 50000000 0.0 0.0 0.0 0.0 randVec.vs' Main 136 10000000 16.2 59.0 16.2 59.0 CAF Main 131 0 0.0 0.0 0.0 0.0 main Main 132 1 0.0 0.0 0.0 0.0 main.l Main 139 1 0.0 0.0 0.0 0.0 main.vs Main 138 0 0.0 0.0 0.0 0.0 CAF GHC.IO.Encoding 112 0 0.0 0.0 0.0 0.0 CAF GHC.IO.Handle.FD 110 0 0.0 0.0 0.0 0.0 CAF GHC.Conc.Signal 96 0 0.0 0.0 0.0 0.0 CAF GHC.IO.Encoding.Iconv 93 0 0.0 0.0 0.0 0.0 CAF GHC.Integer.Logarithms.Internals 74 0 0.0 0.0 0.0 0.0
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe