plunder

Unnamed repository; edit this file 'description' to name the repository.
Log | Files | Refs | README | LICENSE

BenchExe.hs (4448B)


      1 -- Copyright 2023 The Plunder Authors
      2 -- Use of this source code is governed by a BSD-style license that can be
      3 -- found in the LICENSE file.
      4 
      5 module Data.Sorted.BenchExe (main) where
      6 
      7 import Criterion.Main
      8 import Nat
      9 import Prelude
     10 import Data.Sorted
     11 import Data.Set (Set)
     12 import qualified Data.Set as S
     13 
     14 import Control.DeepSeq (force)
     15 import Control.Exception (evaluate)
     16 import Data.ByteString (ByteString)
     17 
     18 
     19 -- Examples --------------------------------------------------------------------
     20 
     21 mkSets :: [Int] -> (ArraySet Int, Set Int)
     22 mkSets ks = (ssetFromList ks, S.fromList ks)
     23 
     24 (t1, t1') = mkSets [1,2,4]
     25 (t2, t2') = mkSets [2,3]
     26 
     27 (s1, s1') = mkSets [1..5]
     28 (s2, s2') = mkSets [2..7]
     29 
     30 (m1, m1') = mkSets [1..999]
     31 (m2, m2') = mkSets $ take 30 [5,10..]
     32 
     33 (b1, b1') = mkSets $ take 512 [1,3..] <> [99999]
     34 (b2, b2') = mkSets $ take 512 [1,4..] <> [99999]
     35 
     36 (ls1, ls1') = mkSets $ [1..1024]
     37 (ls2, ls2') = mkSets $ take 7 [3,5..]
     38 
     39 (lS1, lS1') = mkSets $ [1..1024]
     40 (lS2, lS2') = mkSets $ [55,66,77]
     41 
     42 
     43 -- Benchmarks ------------------------------------------------------------------
     44 
     45 -- TODO: Can our intersection be faster on small examples too?
     46 
     47 main :: IO ()
     48 main = do
     49   evaluate $ force ( (t1, s2, t1', s2')
     50                    , (s1, s2, s1', s2')
     51                    , (m1, m2, m1', m2')
     52                    , (b1, b2, b1', b2')
     53                    , (ls1, ls2, ls1', ls2')
     54                    , (lS1, lS2, lS1', lS2')
     55                    )
     56   defaultMain
     57     [ bgroup "set-insert"
     58         [ bench "t0.mem" $ whnf (ssetMember 0) t1
     59         , bench "t0.new" $ whnf (ssetInsert 0) t1
     60         , bench "t0.std" $ whnf (S.insert 0) t1'
     61 
     62         , bench "t1.mem" $ whnf (ssetMember 1) t1
     63         , bench "t1.new" $ whnf (ssetInsert 1) t1
     64         , bench "t1.std" $ whnf (S.insert 1) t1'
     65 
     66         , bench "t2.mem" $ whnf (ssetMember 2) t1
     67         , bench "t2.new" $ whnf (ssetInsert 2) t1
     68         , bench "t2.std" $ whnf (S.insert 2) t1'
     69 
     70         , bench "t3.mem" $ whnf (ssetMember 3) t1
     71         , bench "t3.new" $ whnf (ssetInsert 3) t1
     72         , bench "t3.std" $ whnf (S.insert 3) t1'
     73 
     74         , bench "t4.mem" $ whnf (ssetMember 4) t1
     75         , bench "t4.new" $ whnf (ssetInsert 4) t1
     76         , bench "t4.std" $ whnf (S.insert 4) t1'
     77 
     78         , bench "t5.mem" $ whnf (ssetMember 5) t1
     79         , bench "t5.new" $ whnf (ssetInsert 5) t1
     80         , bench "t5.std" $ whnf (S.insert 5) t1'
     81 
     82         , bench "m0.new" $ whnf (ssetInsert 0) m1
     83         , bench "m0.std" $ whnf (S.insert 0) m1'
     84 
     85         , bench "m1.new" $ whnf (ssetInsert 1) m1
     86         , bench "m1.std" $ whnf (S.insert 1) m1'
     87 
     88         , bench "m500.new" $ whnf (ssetInsert 500) m1
     89         , bench "m500.std" $ whnf (S.insert 500) m1'
     90 
     91         , bench "m1000.new" $ whnf (ssetInsert 1000) m1
     92         , bench "m1000.std" $ whnf (S.insert 1000) m1'
     93         ]
     94 
     95     , bgroup "set-union"
     96         [ bench "tin.new" $ whnf (ssetUnion t1) t2
     97         , bench "tin.std" $ whnf (S.union t1') t2'
     98 
     99         , bench "sml.new" $ whnf (ssetUnion s1) s2
    100         , bench "sml.std" $ whnf (S.union s1') s2'
    101 
    102         , bench "mid.new" $ whnf (ssetUnion m1) m2
    103         , bench "mid.std" $ whnf (S.union m1') m2'
    104 
    105         , bench "big.new" $ whnf (ssetUnion b1) b2
    106         , bench "big.std" $ whnf (S.union b1') b2'
    107 
    108         , bench "skw.new" $ whnf (ssetUnion ls1) ls2
    109         , bench "skw.std" $ whnf (S.union ls1') ls2'
    110         , bench "skw.dts" $ whnf (S.union ls2') ls1'
    111 
    112         , bench "SKW.new" $ whnf (ssetUnion lS1) lS2
    113         , bench "SKW.std" $ whnf (S.union lS1') lS2'
    114         , bench "SKW.dts" $ whnf (S.union lS2') lS1'
    115         ]
    116 
    117     , bgroup "set-intersection"
    118         [ bench "tin.new" $ whnf (ssetIntersection t1) t2
    119         , bench "tin.std" $ whnf (S.intersection t1') t2'
    120 
    121         , bench "sml.new" $ whnf (ssetIntersection s1) s2
    122         , bench "sml.std" $ whnf (S.intersection s1') s2'
    123 
    124         , bench "mid.new" $ whnf (ssetIntersection m1) m2
    125         , bench "mid.std" $ whnf (S.intersection m1') m2'
    126 
    127         , bench "big.new" $ whnf (ssetIntersection b1) b2
    128         , bench "big.std" $ whnf (S.intersection b1') b2'
    129 
    130         , bench "skw.new" $ whnf (ssetIntersection ls1) ls2
    131         , bench "skw.std" $ whnf (S.intersection ls1') ls2'
    132         , bench "skw.dts" $ whnf (S.intersection ls2') ls1'
    133 
    134         , bench "SKW.new" $ whnf (ssetIntersection lS1) lS2
    135         , bench "SKW.std" $ whnf (S.intersection lS1') lS2'
    136         , bench "SKW.dts" $ whnf (S.intersection lS2') lS1'
    137         ]
    138     ]