|
| 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 |
0 commit comments