Skip to content

Commit 7415257

Browse files
committed
Add benchmarks for Mutable.(next|prev)Permutation
Implement benchmarks to test performance of nextPermutation and prevPermutation on mutable vectors. Tests include: - Looping through all permutations on small vectors - Applying bijective versions n times on: - Ascending permutations of size n - Descending permutations of size n - Random permutations of size n - For a baseline, copying a vector of size n once. Benchmarks for bijective permutations begins with such a copy, and you might want to remove the impact of copying from the results. Benchmarks cover both forward (next) and reverse (prev) operations.
1 parent b21bf11 commit 7415257

File tree

4 files changed

+137
-10
lines changed

4 files changed

+137
-10
lines changed
Lines changed: 122 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,122 @@
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE FlexibleContexts #-}
3+
module Bench.Vector.Algo.NextPermutation (generatePermTests) where
4+
5+
import qualified Data.Vector.Unboxed as V
6+
import qualified Data.Vector.Unboxed.Mutable as M
7+
import qualified Data.Vector.Generic.Mutable as G
8+
import System.Random.Stateful
9+
( StatefulGen, UniformRange(uniformRM) )
10+
11+
-- | Generate a list of benchmarks for permutation algorithms.
12+
-- The list contains pairs of benchmark names and corresponding actions.
13+
-- The actions are to be executed by the benchmarking framework.
14+
--
15+
-- The list contains the following benchmarks:
16+
-- - @(next|prev)Permutation@ on a small vector repeated until the end of the permutation cycle
17+
-- - Bijective versions of @(next|prev)Permutation@ on a vector of size @n@, repeated @n@ times
18+
-- - ascending permutation
19+
-- - descending permutation
20+
-- - random permutation
21+
-- - Baseline for bijective versions: just copying a vector of size @n@. Note that the tests for
22+
-- bijective versions begins with copying a vector.
23+
generatePermTests :: StatefulGen g IO => g -> Int -> IO [(String, IO ())]
24+
generatePermTests gen useSize = do
25+
let !k = useSizeToPermLen useSize
26+
let !vasc = V.generate useSize id
27+
!vdesc = V.generate useSize (useSize-1-)
28+
!vrnd <- randomPermutationWith gen useSize
29+
return
30+
[ ("nextPermutation (small vector, until end)", loopPermutations k)
31+
, ("nextPermutationBijective (ascending perm of size n, n times)", repeatNextPermutation vasc useSize)
32+
, ("nextPermutationBijective (descending perm of size n, n times)", repeatNextPermutation vdesc useSize)
33+
, ("nextPermutationBijective (random perm of size n, n times)", repeatNextPermutation vrnd useSize)
34+
, ("prevPermutation (small vector, until end)", loopRevPermutations k)
35+
, ("prevPermutationBijective (ascending perm of size n, n times)", repeatPrevPermutation vasc useSize)
36+
, ("prevPermutationBijective (descending perm of size n, n times)", repeatPrevPermutation vdesc useSize)
37+
, ("prevPermutationBijective (random perm of size n, n times)", repeatPrevPermutation vrnd useSize)
38+
, ("baseline for *Bijective (just copying the vector of size n)", V.thaw vrnd >> return ())
39+
]
40+
41+
-- | Given a PRNG and a length @n@, generate a random permutation of @[0..n-1]@.
42+
randomPermutationWith :: (StatefulGen g IO) => g -> Int -> IO (V.Vector Int)
43+
randomPermutationWith gen n = do
44+
v <- M.generate n id
45+
V.forM_ (V.generate (n-1) id) $ \ !i -> do
46+
j <- uniformRM (i,n-1) gen
47+
M.swap v i j
48+
V.unsafeFreeze v
49+
50+
-- | Given @useSize@ benchmark option, compute the largest @n <= 12@ such that @n! <= useSize@.
51+
-- Repeat-nextPermutation-until-end benchmark will use @n@ as the length of the vector.
52+
-- Note that 12 is the largest @n@ such that @n!@ can be represented as an 'Int32'.
53+
useSizeToPermLen :: Int -> Int
54+
useSizeToPermLen us = case V.findIndex (> max 0 us) $ V.scanl' (*) 1 $ V.generate 12 (+1) of
55+
Just i -> i-1
56+
Nothing -> 12
57+
58+
-- | A bijective version of @G.nextPermutation@ that reverses the vector
59+
-- if it is already in descending order.
60+
-- "Bijective" here means that the function forms a cycle over all permutations
61+
-- of the vector's elements.
62+
--
63+
-- This has a nice property that should be benchmarked:
64+
-- this function takes amortized constant time each call,
65+
-- if successively called either Omega(n) times on a single vector having distinct elements,
66+
-- or arbitrary times on a single vector initially in strictly ascending order.
67+
nextPermutationBijective :: (G.MVector v a, Ord a) => v G.RealWorld a -> IO Bool
68+
nextPermutationBijective v = do
69+
res <- G.nextPermutation v
70+
if res then return True else G.reverse v >> return False
71+
72+
-- | A bijective version of @G.prevPermutation@ that reverses the vector
73+
-- if it is already in ascending order.
74+
-- "Bijective" here means that the function forms a cycle over all permutations
75+
-- of the vector's elements.
76+
--
77+
-- This has a nice property that should be benchmarked:
78+
-- this function takes amortized constant time each call,
79+
-- if successively called either Omega(n) times on a single vector having distinct elements,
80+
-- or arbitrary times on a single vector initially in strictly descending order.
81+
prevPermutationBijective :: (G.MVector v a, Ord a) => v G.RealWorld a -> IO Bool
82+
prevPermutationBijective v = do
83+
res <- G.prevPermutation v
84+
if res then return True else G.reverse v >> return False
85+
86+
-- | Repeat @nextPermutation@ on @[0..n-1]@ until the end.
87+
loopPermutations :: Int -> IO ()
88+
loopPermutations n = do
89+
v <- M.generate n id
90+
let loop = do
91+
res <- M.nextPermutation v
92+
if res then loop else return ()
93+
loop
94+
95+
-- | Repeat @prevPermutation@ on @[n-1,n-2..0]@ until the end.
96+
loopRevPermutations :: Int -> IO ()
97+
loopRevPermutations n = do
98+
v <- M.generate n (n-1-)
99+
let loop = do
100+
res <- M.prevPermutation v
101+
if res then loop else return ()
102+
loop
103+
104+
-- | Repeat @nextPermutationBijective@ on a given vector given times.
105+
repeatNextPermutation :: V.Vector Int -> Int -> IO ()
106+
repeatNextPermutation !v !n = do
107+
!mv <- V.thaw v
108+
let loop !i | i <= 0 = return ()
109+
loop !i = do
110+
_ <- nextPermutationBijective mv
111+
loop (i-1)
112+
loop n
113+
114+
-- | Repeat @prevPermutationBijective@ on a given vector given times.
115+
repeatPrevPermutation :: V.Vector Int -> Int -> IO ()
116+
repeatPrevPermutation !v !n = do
117+
!mv <- V.thaw v
118+
let loop !i | i <= 0 = return ()
119+
loop !i = do
120+
_ <- prevPermutationBijective mv
121+
loop (i-1)
122+
loop n

vector/benchmarks/Main.hs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,17 @@
11
{-# LANGUAGE BangPatterns #-}
22
module Main where
33

4-
import Bench.Vector.Algo.MutableSet (mutableSet)
5-
import Bench.Vector.Algo.ListRank (listRank)
6-
import Bench.Vector.Algo.Rootfix (rootfix)
7-
import Bench.Vector.Algo.Leaffix (leaffix)
8-
import Bench.Vector.Algo.AwShCC (awshcc)
9-
import Bench.Vector.Algo.HybCC (hybcc)
10-
import Bench.Vector.Algo.Quickhull (quickhull)
11-
import Bench.Vector.Algo.Spectral (spectral)
12-
import Bench.Vector.Algo.Tridiag (tridiag)
13-
import Bench.Vector.Algo.FindIndexR (findIndexR, findIndexR_naive, findIndexR_manual)
4+
import Bench.Vector.Algo.MutableSet (mutableSet)
5+
import Bench.Vector.Algo.ListRank (listRank)
6+
import Bench.Vector.Algo.Rootfix (rootfix)
7+
import Bench.Vector.Algo.Leaffix (leaffix)
8+
import Bench.Vector.Algo.AwShCC (awshcc)
9+
import Bench.Vector.Algo.HybCC (hybcc)
10+
import Bench.Vector.Algo.Quickhull (quickhull)
11+
import Bench.Vector.Algo.Spectral (spectral)
12+
import Bench.Vector.Algo.Tridiag (tridiag)
13+
import Bench.Vector.Algo.FindIndexR (findIndexR, findIndexR_naive, findIndexR_manual)
14+
import Bench.Vector.Algo.NextPermutation (generatePermTests)
1415

1516
import Bench.Vector.TestData.ParenTree (parenTree)
1617
import Bench.Vector.TestData.Graph (randomGraph)
@@ -50,6 +51,7 @@ main = do
5051
!ds <- randomVector useSize
5152
!sp <- randomVector (floor $ sqrt $ fromIntegral useSize)
5253
vi <- MV.new useSize
54+
permTests <- generatePermTests gen useSize
5355

5456
defaultMainWithIngredients ingredients $ bgroup "All"
5557
[ bench "listRank" $ whnf listRank useSize
@@ -66,4 +68,5 @@ main = do
6668
, bench "findIndexR_manual" $ whnf findIndexR_manual ((<indexFindThreshold), as)
6769
, bench "minimumOn" $ whnf (U.minimumOn (\x -> x*x*x)) as
6870
, bench "maximumOn" $ whnf (U.maximumOn (\x -> x*x*x)) as
71+
, bgroup "(next|prev)Permutation" $ map (\(name, act) -> bench name $ whnfIO act) permTests
6972
]

vector/changelog.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
The implementation has also been algorithmically updated: in the previous implementation
88
the full enumeration of all the permutations of `[1..n]` took Omega(n*n!), but it now takes O(n!).
99
* Add tests for `{next,prev}Permutation`
10+
* Add benchmarks for `{next,prev}Permutation`
1011

1112
# Changes in version 0.13.1.0
1213

vector/vector.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -286,6 +286,7 @@ library benchmarks-O2
286286
Bench.Vector.Algo.Spectral
287287
Bench.Vector.Algo.Tridiag
288288
Bench.Vector.Algo.FindIndexR
289+
Bench.Vector.Algo.NextPermutation
289290
Bench.Vector.TestData.ParenTree
290291
Bench.Vector.TestData.Graph
291292
Bench.Vector.Tasty

0 commit comments

Comments
 (0)