|
2 | 2 |
|
3 | 3 | module Main where |
4 | 4 |
|
5 | | -import Data.Int ( Int64 ) |
6 | | -import System.Random ( Random, newStdGen, randoms ) |
7 | | -import Data.Proxy ( Proxy(..) ) |
8 | | -import Control.DeepSeq ( NFData, force ) |
9 | 5 | import Data.List.Split ( splitOn ) |
10 | 6 | import System.Environment ( getArgs ) |
11 | | -import Control.Monad ( unless, replicateM ) |
12 | | -import Text.Read |
13 | | -import Linear.Common |
14 | | -import Types as T |
| 7 | +import Control.Monad ( unless ) |
15 | 8 |
|
16 | | -import qualified Data.Primitive.Types as P |
| 9 | +import qualified Array as A |
| 10 | +import qualified Vector as V |
| 11 | +import Input |
17 | 12 | import qualified Measure as M |
18 | | -import qualified Insertion as I |
19 | | -import qualified QuickSort as Q |
20 | | -import qualified DpsMergeSort4 as DMS |
21 | | -import qualified DpsMergeSort4Par as DMSP |
22 | | -import qualified PiecewiseFallbackSort as PFS |
23 | | -import qualified PiecewiseFallbackSortPar as PFSP |
| 13 | +import Sort |
| 14 | +import Utils |
24 | 15 | import qualified Microbench as MB |
25 | | -import qualified Array as A |
26 | | -import qualified Data.Vector.Unboxed as V |
27 | | -import qualified Data.Vector.Algorithms.Insertion as ISDVS |
28 | | -import qualified Data.Vector.Algorithms.Merge as MSDVS |
29 | | -import qualified Data.Vector.Algorithms.Intro as QSDVS |
30 | | - |
31 | | --------------------------------------------------------------------------------- |
32 | | - |
33 | | -getInput :: Benchmark -> Maybe Int -> IO (Input Int64) |
34 | | -getInput bench mb_size = case bench of |
35 | | - GenerateArray -> pure $ IntIn (mb 10000000) |
36 | | - FillArray -> pure $ EltsIn (mb 10000000) 1024 |
37 | | - CopyArray -> pure $ ArrayIn (A.make (mb 10000000) 1) |
38 | | - SumArray -> pure $ ArrayIn (A.make (mb 10000000) 1) |
39 | | - Fib -> pure $ IntIn (mb 45) |
40 | | - OurSort alg -> case alg of |
41 | | - Insertionsort -> ArrayIn <$> randArray (Proxy :: Proxy Int64) (mb 100) |
42 | | - Quicksort -> ArrayIn <$> randArray (Proxy :: Proxy Int64) (mb 1000000) |
43 | | - Mergesort -> ArrayIn <$> randArray (Proxy :: Proxy Int64) (mb 8000000) |
44 | | - Optsort -> ArrayIn <$> randArray (Proxy :: Proxy Int64) (mb 8000000) |
45 | | - _ -> error "getInput: Unexpected Input!" |
46 | | - where |
47 | | - mb x = case mb_size of |
48 | | - Nothing -> x |
49 | | - Just y -> y |
50 | | - |
51 | | -getInputAsDataVector :: SortAlgo -> Maybe Int -> IO Vec |
52 | | -getInputAsDataVector bench mb_size = case bench of |
53 | | - Insertionsort -> V.fromList <$> randList (Proxy :: Proxy Int64) (mb 100) |
54 | | - Quicksort -> V.fromList <$> randList (Proxy :: Proxy Int64) (mb 1000000) |
55 | | - Mergesort -> V.fromList <$> randList (Proxy :: Proxy Int64) (mb 8000000) |
56 | | - _ -> error "getInputAsDataVector: TODO sort function not implemented!" |
57 | | - where |
58 | | - mb x = case mb_size of |
59 | | - Nothing -> x |
60 | | - Just y -> y |
61 | | - |
62 | | -getInputAsList :: SortAlgo -> Maybe Int -> IO [Int64] |
63 | | -getInputAsList bench mb_size = case bench of |
64 | | - Insertionsort -> randList (Proxy :: Proxy Int64) (mb 100) |
65 | | - Quicksort -> randList (Proxy :: Proxy Int64) (mb 1000000) |
66 | | - Mergesort -> randList (Proxy :: Proxy Int64) (mb 8000000) |
67 | | - _ -> error "getInputAsDataVector: TODO sort function not implemented!" |
68 | | - where |
69 | | - mb x = case mb_size of |
70 | | - Nothing -> x |
71 | | - Just y -> y |
72 | | - |
73 | | -copyInput :: (Input Int64) -> IO (Input Int64) |
74 | | -copyInput i = case i of |
75 | | - ArrayIn arr -> pure $ ArrayIn (A.copy arr 0 (A.make (A.size arr) (A.get arr 0)) 0 (A.size arr)) |
76 | | - _ -> error "TODO: copyInput not implemented!" |
77 | | - |
78 | | -copyInputIterTimes :: Input Int64 -> Int -> IO [A.Array Int64] |
79 | | -copyInputIterTimes inp iters = do |
80 | | - copiedInputs <- replicateM iters (copyInput inp) |
81 | | - return [arr | ArrayIn arr <- copiedInputs] |
82 | 16 |
|
83 | | -randArray :: forall a. (Random a, NFData a, P.Prim a) => Proxy a -> Int -> IO (A.Array a) |
84 | | -randArray _ty size = do |
85 | | - rng <- newStdGen |
86 | | - let ls :: [a] |
87 | | - ls = take size $ randoms rng |
88 | | - !arr = force (A.fromList ls) |
89 | | - pure arr |
90 | | - |
91 | | -randList :: forall a. (Random a, NFData a) => Proxy a -> Int -> IO [a] |
92 | | -randList _ty size = do |
93 | | - rng <- newStdGen |
94 | | - let ls :: [a] |
95 | | - ls = take size $ randoms rng |
96 | | - pure (force ls) |
97 | | - |
98 | | -sortFn :: (Show a, A.HasPrimOrd a, NFData a) => SortAlgo -> ParOrSeq -> (A.Array a -. A.Array a) |
99 | | -sortFn bench parorseq = case (bench,parorseq) of |
100 | | - (Insertionsort, Seq) -> I.isort_top' |
101 | | - (Quicksort, Seq) -> Q.quickSort' |
102 | | - (Mergesort, Seq) -> DMS.msort |
103 | | - (Mergesort, Par) -> DMSP.msort |
104 | | - (Optsort, Seq) -> PFS.pfsort |
105 | | - (Optsort, Par) -> PFSP.pfsort |
106 | | - oth -> error $ "sortFn: unknown configuration: " ++ show oth |
107 | | - |
108 | | -vectorSortFn :: SortAlgo -> ParOrSeq -> VecSort |
109 | | -vectorSortFn bench parorseq = case (bench,parorseq) of |
110 | | - (Insertionsort, Seq) -> ISDVS.sort |
111 | | - (Mergesort, Seq) -> MSDVS.sort |
112 | | - (Quicksort, Seq) -> QSDVS.sort |
113 | | - oth -> error $ "sortFn: unknown configuration: " ++ show oth |
114 | | - |
115 | | --------------------------------------------------------------------------------- |
116 | | - |
117 | | -isSorted :: Ord a => [a] -> Bool |
118 | | -isSorted [] = True |
119 | | -isSorted [_] = True |
120 | | -isSorted (x:y:xs) = x <= y && isSorted (y:xs) |
121 | | - |
122 | | -readBench :: String -> Benchmark |
123 | | -readBench s = case readMaybe s of |
124 | | - Just b -> b |
125 | | - Nothing -> case readMaybe s of |
126 | | - Just srt -> OurSort srt |
127 | | - Nothing -> read s |
128 | 17 |
|
129 | 18 | -- dobench :: Benchmark -> ParOrSeq -> Maybe Int -> IO () |
130 | 19 | dobench :: Benchmark -> ParOrSeq -> Maybe Int -> Int -> IO () |
@@ -204,11 +93,10 @@ dobench bench parorseq mb_size iters = do |
204 | 93 | putStrLn "Sorted: OK" |
205 | 94 | pure (V.length inPutVec, V.length res0, tmed0, tall0) |
206 | 95 | OurSort alg -> do |
207 | | - ArrayIn arr <- getInput bench mb_size |
208 | | - arrs <- copyInputIterTimes (ArrayIn arr) iters |
| 96 | + (ArrayIn arr) <- getInput bench mb_size |
209 | 97 | let fn = sortFn alg parorseq |
210 | 98 | putStrLn $ "array size = " ++ show (A.size arr) |
211 | | - (res0, tmed0, tall0) <- M.benchOnArrays fn arrs |
| 99 | + (res0, tmed0, tall0) <- M.benchOnArrays fn arr iters |
212 | 100 | unless (isSorted (A.toList res0)) (error $ show bench ++ ": result not sorted.") |
213 | 101 | putStrLn "Sorted: OK" |
214 | 102 | pure (A.size arr, A.size res0, tmed0, tall0) |
|
0 commit comments