Skip to content

Commit 0f60257

Browse files
authored
Merge pull request #548 from Shimuuar/test-traverse-optimizations
Optimization test which use allocation for testing optimizer
2 parents 4861108 + fc83758 commit 0f60257

File tree

5 files changed

+166
-2
lines changed

5 files changed

+166
-2
lines changed
Lines changed: 102 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,102 @@
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
{-# LANGUAGE TypeApplications #-}
5+
{- |
6+
Here we test that GHC is able to optimize well construction of vector
7+
using monadic\/applicative actions. Well is understood as able to
8+
generate code which does not allocate except for buffer and some
9+
constant overhead.
10+
-}
11+
module Inspect.Alloc where
12+
13+
import Control.Monad.ST
14+
import Data.Int
15+
-- import Data.Monoid
16+
import Data.Functor.Identity
17+
import Test.Tasty
18+
import Test.Tasty.HUnit
19+
import System.Mem
20+
import Test.Alloc
21+
22+
import qualified Data.Vector.Unboxed as VU
23+
24+
25+
tests :: TestTree
26+
tests = testGroup "allocations"
27+
[ testGroup "traversable"
28+
[ testCase "IO"
29+
$ checkAllocations (linear 8)
30+
$ whnfIO (VU.traverse (\_ -> getAllocationCounter) vector)
31+
32+
#if MIN_VERSION_base(4,17,0)
33+
-- GHC<9.4 doesn't optimize well.
34+
, testCase "ST"
35+
$ checkAllocations (linear 8)
36+
$ (\v -> runST $ VU.traverse (pureST . fromIntegral) v) `whnf` vector
37+
#endif
38+
39+
#if MIN_VERSION_base(4,15,0)
40+
-- GHC<9.0 doesn't optimize this well. And there's no appetite
41+
-- for finding out why. Thus it's disabled for them. We'll still
42+
-- catch regression going forward.
43+
, testCase "Identity"
44+
$ checkAllocations (linear 8)
45+
$ VU.traverse (\n -> Identity (10*n)) `whnf` vector
46+
#endif
47+
48+
-- NOTE: Naive traversal is lazy and allocated 2 words per element
49+
--
50+
-- , testCase "Const Sum"
51+
-- $ checkAllocations constant
52+
-- $ whnf (VU.traverse (Const @_ @() . Sum)) vector
53+
]
54+
, testGroup "unstreamM"
55+
[ testCase "IO"
56+
$ checkAllocations (linear 8)
57+
$ whnfIO (VU.replicateM size getAllocationCounter)
58+
59+
#if MIN_VERSION_base(4,17,0)
60+
-- GHC<9.4 doesn't optimize well.
61+
, testCase "ST"
62+
$ checkAllocations (linear 8)
63+
$ (\sz -> runST $ VU.generateM sz pureST) `whnf` size
64+
#endif
65+
66+
-- , testCase "Identity"
67+
-- $ checkAllocations (linear 8)
68+
-- $ (\sz -> VU.generateM sz (\n -> Identity (fromIntegral n :: Int64))) `whnf` size
69+
]
70+
]
71+
72+
73+
pureST :: Int -> ST s Int64
74+
{-# NOINLINE pureST #-}
75+
pureST i = pure $! fromIntegral i
76+
77+
-- | Constant overhead. Measurement precision is 4k
78+
overhead :: Int64
79+
overhead = 4096*2
80+
81+
-- | Vector size. It should be large so 1byte per element will be
82+
-- large than page.
83+
size :: Int
84+
size = 100000
85+
86+
vector :: VU.Vector Int64
87+
{-# NOINLINE vector #-}
88+
vector = VU.generate size fromIntegral
89+
90+
-- | N bytes per element + constant overhead. We also check that bound
91+
-- is tight.
92+
linear :: Int -> Range
93+
linear n = Range
94+
{ allocHi = fromIntegral (n * size) + overhead
95+
, allocLo = fromIntegral (n * size)
96+
}
97+
98+
-- | Only constant overhead
99+
constant :: Range
100+
constant = Range { allocHi = overhead
101+
, allocLo = 0
102+
}

vector/tests-inspect/Test/Alloc.hs

Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
{-# LANGUAGE RecordWildCards #-}
2+
-- |
3+
-- Test that function allocates is in range. This is good way to test
4+
-- that GHC produces tight non-allocating loops.
5+
module Test.Alloc where
6+
7+
import Control.Exception
8+
import Data.Int
9+
import System.Mem
10+
import Test.Tasty.HUnit
11+
import Text.Printf
12+
13+
----------------------------------------------------------------
14+
-- Benchmarking machinery copied from tasty-bench
15+
----------------------------------------------------------------
16+
17+
newtype Benchmarkable = Benchmarkable (IO ())
18+
19+
whnf :: (a -> b) -> a -> Benchmarkable
20+
{-# NOINLINE whnf #-}
21+
whnf f a = Benchmarkable $ do _ <- evaluate (f a)
22+
return ()
23+
24+
whnfIO :: IO a -> Benchmarkable
25+
{-# NOINLINE whnfIO #-}
26+
whnfIO io = Benchmarkable $ do _ <- evaluate =<< io
27+
return ()
28+
29+
30+
-- | Measure allocations. Measurements use 'getAllocationCounter' so
31+
-- it's accurate up to 4k bytes.
32+
allocations :: Benchmarkable -> IO Int64
33+
allocations (Benchmarkable io) = do
34+
-- We need to run `io` twice in order to ensure that all constant
35+
-- parameters are evaluated.
36+
io
37+
n1 <- getAllocationCounter
38+
io
39+
n2 <- getAllocationCounter
40+
return $! n1 - n2
41+
42+
43+
-- | Expected allocations range
44+
data Range = Range { allocLo :: !Int64
45+
, allocHi :: !Int64
46+
}
47+
deriving Show
48+
49+
-- | Check that computation's allocations lie in range
50+
checkAllocations :: Range -> Benchmarkable -> IO ()
51+
checkAllocations Range{..} bench = do
52+
alloc <- allocations bench
53+
let msg = unlines [ printf "allocated = %12d" alloc
54+
, printf "Low bound = %12d" allocLo
55+
, printf "Hi bound = %12d" allocHi
56+
]
57+
assertBool msg $ alloc <= allocHi
58+
&& alloc >= allocLo
59+

vector/tests-inspect/main.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,13 @@
11
module Main (main) where
22

33
import qualified Inspect
4+
import qualified Inspect.Alloc
45
import qualified Inspect.DerivingVia
56
import Test.Tasty (defaultMain,testGroup)
67

78
main :: IO ()
89
main = defaultMain $ testGroup "tests"
910
[ Inspect.tests
1011
, Inspect.DerivingVia.tests
12+
, Inspect.Alloc.tests
1113
]

vector/tests/Utilities.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -266,8 +266,6 @@ xs // ps = go xs ps' 0
266266
go [] _ _ = []
267267

268268

269-
-- withIndexFirst :: (Int -> a -> [a]) -> [a] -> [a]
270-
271269
withIndexFirst :: (((Int, a) -> b) -> [(Int, a)] -> c)
272270
-> ((Int -> a -> b) -> [a] -> c)
273271
withIndexFirst m f = m (uncurry f) . zip [0::Int ..]

vector/vector.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -252,13 +252,16 @@ test-suite vector-inspection
252252
main-is: main.hs
253253
default-language: Haskell2010
254254
Other-modules: Inspect
255+
Inspect.Alloc
255256
Inspect.DerivingVia
256257
Inspect.DerivingVia.OtherFoo
258+
Test.Alloc
257259
build-depends:
258260
base -any
259261
, primitive >= 0.6.4.0 && < 0.10
260262
, vector -any
261263
, tasty
264+
, tasty-hunit
262265
, tasty-inspection-testing >= 0.1
263266

264267
library benchmarks-O2

0 commit comments

Comments
 (0)