Created
July 18, 2013 05:59
-
-
Save amosr/6026995 to your computer and use it in GitHub Desktop.
stack overflow conversion to Data.Vector: runs in ~6ms.
http://stackoverflow.com/questions/17714947/why-does-haskell-perform-so-poorly-when-executing-c-like-codes-in-this-instanc/17715424
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import qualified Data.Vector.Unboxed as U | |
import Data.List | |
import System.Random | |
import System.CPUTime | |
import Text.Printf | |
import Control.Exception | |
main :: IO () | |
main = do let (!x,!y) = initArrays | |
-- seq the array. bang wasn't working? | |
print (U.unsafeIndex x 0, U.unsafeIndex y 0) | |
area <- time (integrate x y) | |
print area | |
n :: Int | |
n = 5000000 | |
maxY :: Float | |
maxY = 100000.0/(fromIntegral n) | |
maxXgap :: Float | |
maxXgap = 1 | |
--initialize arrays with random floats | |
--this part is not measured in the running time (very slow) | |
initArrays :: (U.Vector Float, U.Vector Float) | |
initArrays = let y = U.fromList (randomList maxY n (mkStdGen 23432)) | |
x = U.fromList (scanl1 (+) $ randomList maxXgap n (mkStdGen 5462)) | |
in (x,y) | |
randomList :: Float -> Int -> StdGen -> [Float] | |
randomList max n gen = map (abs . ((*) max)) (take n . unfoldr (Just . random) $ gen) | |
integrate :: U.Vector Float -> U.Vector Float -> IO Float | |
integrate x y = let !r = iterative x y 0 0 | |
in return r | |
iterative :: U.Vector Float -> U.Vector Float -> Int -> Float -> Float | |
iterative x y !i !accum = if i == n-1 | |
then accum | |
else let x1 = U.unsafeIndex x i | |
x2 = U.unsafeIndex x (i+1) | |
y1 = U.unsafeIndex y i | |
y2 = U.unsafeIndex y (i+1) | |
in iterative x y (i+1) (accum + (y2+y1)/2*(x2-x1)) | |
time :: IO t -> IO t | |
time a = do | |
start <- getCPUTime | |
v <- a | |
end <- getCPUTime | |
let diff = (fromIntegral (end-start)) / (10^9) | |
printf "Computation time %0.5f ms\n" (diff :: Double) | |
return v |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment