Created
November 30, 2013 16:37
-
-
Save llelf/7721211 to your computer and use it in GitHub Desktop.
This file contains 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
{-# LANGUAGE ForeignFunctionInterface #-} | |
import System.Environment | |
import qualified Data.Vector as V | |
import Control.Monad (join) | |
import Data.Word | |
import Criterion.Main | |
import Foreign.C | |
import Foreign.Marshal | |
import Foreign.Ptr | |
foreign import ccall "result_c" _result_c :: Int -> Ptr Int -> Ptr Int -> IO Int | |
result_c n = alloca (\x -> _result_c n x x) | |
foreign import ccall "result_llvm" _result_llvm :: Int -> Ptr Int -> Ptr Int -> IO Int | |
result_llvm n = alloca (\x -> _result_llvm n x x) | |
type W = Word32 | |
next a = Just . join (,) $ (if even a then a else 3*a+1) `div` 2 | |
len = (+1) . V.length . V.takeWhile (/=1) . V.unfoldr next | |
result :: W -> (Int,W) | |
result = V.maximum . V.map (\x -> (len x, x)) . V.enumFromTo 1 | |
main' = do | |
[a0] <- getArgs | |
let max_a0 = read a0 :: W | |
print . result $ max_a0 | |
main = defaultMain . map group $ [100000,250000,500000,1000000] | |
where group n = bgroup (show n) [ | |
bench "data.vector" $ nf result n, | |
bench "gcc -O2" $ nfIO (result_c (fromIntegral n)), | |
bench "llvm -O2" $ nfIO (result_llvm (fromIntegral n)) | |
] | |
-- main = do r <- result_c 100000 | |
-- print (r, result 100000) | |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment