Skip to content

Commit

Permalink
Make benchmark compatible with older primitive
Browse files Browse the repository at this point in the history
This is necessary to allow testing with lts-9 snapshot, since stack is
still capable of installing ghc-8.0 and ghc-8.2, while ghcup is having
issues in achieving that on CI
  • Loading branch information
lehins committed Dec 14, 2024
1 parent 2d76a11 commit 13db6f6
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 5 deletions.
16 changes: 12 additions & 4 deletions bench/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main (main) where
Expand All @@ -13,9 +14,11 @@ import Foreign.C.Types
import Numeric.Natural (Natural)
import System.Random.SplitMix as SM
import Test.Tasty.Bench
#if MIN_VERSION_primitive(0,7,1)
import Control.Monad.Primitive
import Data.Primitive.PrimArray
import Data.Primitive.Types
import Data.Primitive.PrimArray
#endif

import System.Random.Stateful

Expand Down Expand Up @@ -198,7 +201,9 @@ main = do
in pureUniformRBench (Proxy :: Proxy Natural) range sz
]
, bgroup "floating"
[ bgroup "IO"
[
#if MIN_VERSION_primitive(0,7,1)
bgroup "IO"
[ env ((,) <$> getStdGen <*> newAlignedPinnedPrimArray sz) $ \ ~(gen, ma) ->
bench "uniformFloat01M" $
nfIO (runStateGenT gen (fillMutablePrimArrayM uniformFloat01M ma))
Expand All @@ -212,7 +217,9 @@ main = do
bench "uniformDoublePositive01M" $
nfIO (runStateGenT gen (fillMutablePrimArrayM uniformDoublePositive01M ma))
]
, bgroup "State"
,
#endif
bgroup "State"
[ env getStdGen $
bench "uniformFloat01M" . nf (`runStateGen` (replicateM_ sz . uniformFloat01M))
, env getStdGen $
Expand Down Expand Up @@ -320,7 +327,7 @@ genMany f g0 n = go 0 $ f g0
| i < n = go (i + 1) $ f g
| otherwise = y


#if MIN_VERSION_primitive(0,7,1)
fillMutablePrimArrayM ::
(Prim a, PrimMonad m)
=> (gen -> m a)
Expand All @@ -334,3 +341,4 @@ fillMutablePrimArrayM f ma g = do
| otherwise = pure ()
go 0
unsafeFreezePrimArray ma
#endif
2 changes: 1 addition & 1 deletion random.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,7 @@ benchmark bench
build-depends:
base,
mtl,
primitive >= 0.7.1,
primitive,
random,
splitmix >=0.1 && <0.2,
tasty-bench

0 comments on commit 13db6f6

Please sign in to comment.