Skip to content

Instantly share code, notes, and snippets.

@jtobin
Created August 22, 2013 04:35
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save jtobin/6303260 to your computer and use it in GitHub Desktop.
Save jtobin/6303260 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
import Control.DeepSeq
import qualified Data.Vector.Unboxed as U
import System.Random.MWC
import Control.Monad
import Criterion.Main
import Criterion.Config
newtype AffineTransform = AffineTransform {
get :: U.Vector Double
} deriving Show
data SP = SP {
one :: {-# UNPACK #-} !Double
, two :: {-# UNPACK #-} !Double
} deriving Show
instance NFData SP where
rnf p = rnf (one p) `seq` rnf (two p) `seq` ()
runAffineTransform :: AffineTransform -> (Double, Double) -> (Double, Double)
runAffineTransform affTr !(!x, !y) =
( get affTr `U.unsafeIndex` 0 * x
+ get affTr `U.unsafeIndex` 1 * y
+ get affTr `U.unsafeIndex` 2
, get affTr `U.unsafeIndex` 3 * x
+ get affTr `U.unsafeIndex` 4 * y
+ get affTr `U.unsafeIndex` 5
)
{-# INLINE runAffineTransform #-}
runAffineTransform2 :: AffineTransform -> SP -> SP
runAffineTransform2 affTr !(SP x y) =
SP ( get affTr `U.unsafeIndex` 0 * x
+ get affTr `U.unsafeIndex` 1 * y
+ get affTr `U.unsafeIndex` 2 )
( get affTr `U.unsafeIndex` 3 * x
+ get affTr `U.unsafeIndex` 4 * y
+ get affTr `U.unsafeIndex` 5 )
{-# INLINE runAffineTransform2 #-}
testAffineTransformSpeed :: AffineTransform -> Int -> (Double, Double)
testAffineTransformSpeed affTr count = go count (0.5, 0.5)
where go :: Int -> (Double, Double) -> (Double, Double)
go 0 res = res
go !n !res = go (n-1) (runAffineTransform affTr res)
testAffineTransformSpeed2 :: AffineTransform -> Int -> SP
testAffineTransformSpeed2 affTr count = go count (SP 0.5 0.5)
where go 0 res = res
go !n !res = go (n - 1) (runAffineTransform2 affTr res)
main :: IO ()
main = do
g <- create
zs <- fmap (AffineTransform . U.fromList)
(replicateM 100000 (uniformR (0 :: Double, 1) g))
let myConfig = defaultConfig { cfgPerformGC = ljust True }
defaultMainWith myConfig (return ()) [
bench "yours" $ nf (testAffineTransformSpeed zs) 10
, bench "mine" $ nf (testAffineTransformSpeed2 zs) 10
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment