Skip to content

Commit a78d659

Browse files
committed
Change structure of examples, tests, bench, and tests-examples to properly match src structure
1 parent 919fc6c commit a78d659

File tree

18 files changed

+99
-92
lines changed

18 files changed

+99
-92
lines changed

bench/Data/Mutable/Array.hs renamed to bench/Bench/Data/Array/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
-- land in a file named “Array.dump-simpl”
1212
-- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dsuppress-all -dsuppress-uniques #-}
1313

14-
module Data.Mutable.Array (benchmarks) where
14+
module Bench.Data.Array.Mutable (benchmarks) where
1515

1616
import Control.DeepSeq (rnf)
1717
import qualified Data.Array.Mutable.Linear as Array.Linear

bench/Data/Mutable/Quicksort.hs renamed to bench/Bench/Data/Array/Mutable/Quicksort.hs

Lines changed: 8 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -1,28 +1,16 @@
11
{-# LANGUAGE NumericUnderscores #-}
22

3-
module Data.Mutable.Quicksort (benchmarks) where
3+
module Bench.Data.Array.Mutable.Quicksort (benchmarks) where
44

55
import Control.DeepSeq (force)
66
import Control.Exception (evaluate)
7+
import Data.Array.Mutable.Quicksort (qsortUsingArray, qsortUsingList)
78
import Data.List (sort)
8-
import Simple.Quicksort (quickSort)
99
import System.Random
1010
import Test.Tasty.Bench
1111

1212
-- Follows thread from https://discourse.haskell.org/t/linear-haskell-quicksort-performance/10280
1313

14-
qs :: (Ord a) => [a] -> [a]
15-
qs [] = []
16-
qs (x : xs) = qs ltx ++ x : qs gex
17-
where
18-
ltx = [y | y <- xs, y < x]
19-
gex = [y | y <- xs, y >= x]
20-
21-
linArrayQuicksort, lazyListQuicksort, stdLibSort :: [Int] -> [Int]
22-
linArrayQuicksort = quickSort
23-
lazyListQuicksort = qs
24-
stdLibSort = sort
25-
2614
gen :: StdGen
2715
gen = mkStdGen 4541645642
2816

@@ -40,12 +28,12 @@ benchmarks =
4028
env (randomListBuilder size) $ \randomList ->
4129
bgroup
4230
("size " ++ (show size))
43-
[ bench "linArrayQuicksort" $
44-
nf linArrayQuicksort randomList,
45-
bench "lazyListQuicksort" $
46-
nf lazyListQuicksort randomList,
47-
bench "stdLibSort" $
48-
nf stdLibSort randomList
31+
[ bench "qsortUsingArray" $
32+
nf qsortUsingArray randomList,
33+
bench "qsortUsingList" $
34+
nf qsortUsingList randomList,
35+
bench "sortStdLib" $
36+
nf sort randomList
4937
]
5038
)
5139
<$> sizes

bench/Data/Mutable/HashMap.hs renamed to bench/Bench/Data/HashMap/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
{-# LANGUAGE StandaloneDeriving #-}
1212
{-# LANGUAGE TupleSections #-}
1313

14-
module Data.Mutable.HashMap (benchmarks) where
14+
module Bench.Data.HashMap.Mutable (benchmarks) where
1515

1616
import Control.DeepSeq (NFData (..), deepseq, force)
1717
import qualified Control.Monad.Random as Random

bench/Main.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,14 @@
11
module Main where
22

3-
import qualified Data.Mutable.Array as Array
4-
import qualified Data.Mutable.HashMap as HashMap
5-
import qualified Data.Mutable.Quicksort as Quicksort
3+
import qualified Bench.Data.Array.Mutable as Array
4+
import qualified Bench.Data.Array.Mutable.Quicksort as Quicksort
5+
import qualified Bench.Data.HashMap.Mutable as HashMap
66
import Test.Tasty.Bench (defaultMain)
77

88
main :: IO ()
99
main = do
1010
defaultMain
1111
[ Array.benchmarks,
12-
HashMap.benchmarks,
13-
Quicksort.benchmarks
12+
Quicksort.benchmarks,
13+
HashMap.benchmarks
1414
]

examples/Simple/Quicksort.hs renamed to examples/Data/Array/Mutable/Quicksort.hs

Lines changed: 24 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
-- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dsuppress-all -dsuppress-uniques #-}
77

88
-- | This module implements quicksort with mutable arrays from linear-base
9-
module Simple.Quicksort where
9+
module Data.Array.Mutable.Quicksort where
1010

1111
import Data.Array.Mutable.Linear (Array)
1212
import qualified Data.Array.Mutable.Linear as Array
@@ -17,15 +17,22 @@ import Prelude.Linear hiding (partition)
1717
-- # Quicksort
1818
-------------------------------------------------------------------------------
1919

20-
quickSort :: [Int] -> [Int]
21-
quickSort xs = unur $ Array.fromList xs $ Array.toList . arrQuicksort
20+
qsortUsingList :: (Ord a) => [a] -> [a]
21+
qsortUsingList [] = []
22+
qsortUsingList (x : xs) = qsortUsingList ltx ++ x : qsortUsingList gex
23+
where
24+
ltx = [y | y <- xs, y < x]
25+
gex = [y | y <- xs, y >= x]
2226

23-
arrQuicksort :: Array Int %1 -> Array Int
24-
arrQuicksort arr =
27+
qsortUsingArray :: (Ord a) => [a] -> [a]
28+
qsortUsingArray xs = unur $ Array.fromList xs $ Array.toList . qsortArray
29+
30+
qsortArray :: (Ord a) => Array a %1 -> Array a
31+
qsortArray arr =
2532
Array.size arr
2633
& \(Ur len, arr1) -> go 0 (len - 1) arr1
2734

28-
go :: Int -> Int -> Array Int %1 -> Array Int
35+
go :: (Ord a) => Int -> Int -> Array a %1 -> Array a
2936
go lo hi arr
3037
| lo >= hi = arr
3138
| otherwise =
@@ -43,23 +50,23 @@ go lo hi arr
4350
-- @arr'[j] > pivot@ for @ix < j <= hi@,
4451
-- @arr'[k] = arr[k]@ for @k < lo@ and @k > hi@, and
4552
-- @arr'@ is a permutation of @arr@.
46-
partition :: Array Int %1 -> Int -> Int -> Int -> (Array Int, Ur Int)
47-
partition arr pivot lx rx
48-
| (rx < lx) = (arr, Ur (lx - 1))
53+
partition :: (Ord a) => Array a %1 -> a -> Int -> Int -> (Array a, Ur Int)
54+
partition arr pivot lo hi
55+
| (hi < lo) = (arr, Ur (lo - 1))
4956
| otherwise =
50-
Array.read arr lx
57+
Array.read arr lo
5158
& \(Ur lVal, arr1) ->
52-
Array.read arr1 rx
59+
Array.read arr1 hi
5360
& \(Ur rVal, arr2) -> case (lVal <= pivot, pivot < rVal) of
54-
(True, True) -> partition arr2 pivot (lx + 1) (rx - 1)
55-
(True, False) -> partition arr2 pivot (lx + 1) rx
56-
(False, True) -> partition arr2 pivot lx (rx - 1)
61+
(True, True) -> partition arr2 pivot (lo + 1) (hi - 1)
62+
(True, False) -> partition arr2 pivot (lo + 1) hi
63+
(False, True) -> partition arr2 pivot lo (hi - 1)
5764
(False, False) ->
58-
swap arr2 lx rx
59-
& \arr3 -> partition arr3 pivot (lx + 1) (rx - 1)
65+
swap arr2 lo hi
66+
& \arr3 -> partition arr3 pivot (lo + 1) (hi - 1)
6067

6168
-- | @swap a i j@ exchanges the positions of values at @i@ and @j@ of @a@.
62-
swap :: (HasCallStack) => Array Int %1 -> Int -> Int -> Array Int
69+
swap :: (HasCallStack) => Array a %1 -> Int -> Int -> Array a
6370
swap arr i j =
6471
Array.read arr i
6572
& \(Ur ival, arr1) ->

examples/Simple/TopSort.hs renamed to examples/Data/HashMap/Mutable/TopSort.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
{-# OPTIONS_GHC -Wno-name-shadowing #-}
66
{-# OPTIONS_GHC -Wno-unused-matches #-}
77

8-
module Simple.TopSort where
8+
module Data.HashMap.Mutable.TopSort where
99

1010
import Data.Bifunctor.Linear (second)
1111
import qualified Data.Functor.Linear as Data

examples/README.md

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
# Examples
22

3+
* `Data`
4+
* These are examples of using the pure linear interface of mutable
5+
data structures provided by linear base.
36
* `Simple`
47
* These are tutorial level examples for understanding linear
58
types and using bread-and-butter tools in linear base.
69
* Recommended order: `Pure`, `FileIO`.
710
* `Foreign`
811
* These are examples of explicitly allocating off the GC heap's
9-
memory and on the system heap's memory
10-
12+
memory and on the system heap's memory.

linear-base.cabal

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -153,8 +153,8 @@ library examples
153153
Foreign.Heap
154154
Simple.FileIO
155155
Simple.Pure
156-
Simple.Quicksort
157-
Simple.TopSort
156+
Data.Array.Mutable.Quicksort
157+
Data.HashMap.Mutable.TopSort
158158
build-depends:
159159
base,
160160
linear-base,
@@ -169,12 +169,12 @@ test-suite test
169169
main-is: Main.hs
170170
hs-source-dirs: test
171171
other-modules:
172-
Test.Data.Destination
173-
Test.Data.Mutable.Array
174-
Test.Data.Mutable.Vector
175-
Test.Data.Mutable.HashMap
176-
Test.Data.Mutable.Set
177-
Test.Data.Polarized
172+
Test.Data.Array.Destination
173+
Test.Data.Array.Mutable
174+
Test.Data.Vector.Mutable
175+
Test.Data.HashMap.Mutable
176+
Test.Data.Set.Mutable
177+
Test.Data.Array.Polarized
178178
Test.Data.Functor.Linear
179179
Test.Data.V
180180
Test.Data.Replicator
@@ -200,7 +200,7 @@ test-suite test-examples
200200
hs-source-dirs: test-examples
201201
other-modules:
202202
Test.Foreign
203-
Test.Simple.Quicksort
203+
Test.Data.Array.Mutable.Quicksort
204204
default-language: Haskell2010
205205
build-depends:
206206
base,
@@ -217,9 +217,9 @@ benchmark bench
217217
main-is: Main.hs
218218
hs-source-dirs: bench
219219
other-modules:
220-
Data.Mutable.HashMap
221-
Data.Mutable.Array
222-
Data.Mutable.Quicksort
220+
Bench.Data.HashMap.Mutable
221+
Bench.Data.Array.Mutable
222+
Bench.Data.Array.Mutable.Quicksort
223223
default-language: Haskell2010
224224
build-depends:
225225
base,

test-examples/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module Main where
22

3+
import Test.Data.Array.Mutable.Quicksort (quicksortTests)
34
import Test.Foreign (foreignGCTests)
4-
import Test.Simple.Quicksort (quickSortTests)
55
import Test.Tasty
66

77
main :: IO ()
@@ -12,5 +12,5 @@ allTests =
1212
testGroup
1313
"All tests"
1414
[ foreignGCTests,
15-
quickSortTests
15+
quicksortTests
1616
]
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module Test.Data.Array.Mutable.Quicksort (quicksortTests) where
4+
5+
import Data.Array.Mutable.Quicksort (qsortUsingArray, qsortUsingList)
6+
import Data.List (sort)
7+
import Hedgehog
8+
import qualified Hedgehog.Gen as Gen
9+
import qualified Hedgehog.Range as Range
10+
import Test.Tasty
11+
import Test.Tasty.Hedgehog (testPropertyNamed)
12+
13+
quicksortTests :: TestTree
14+
quicksortTests =
15+
testGroup
16+
"quicksort tests"
17+
[ testPropertyNamed "sort xs === qsortUsingArray xs" "testQsortUsingArray" testQsortUsingArray,
18+
testPropertyNamed "sort xs === qsortUsingList xs" "testQsortUsingList" testQsortUsingList
19+
]
20+
21+
testQsortUsingArray :: Property
22+
testQsortUsingArray = property $ do
23+
xs <- forAll $ Gen.list (Range.linear 0 1000) (Gen.int $ Range.linear 0 100)
24+
sort xs === qsortUsingArray xs
25+
26+
testQsortUsingList :: Property
27+
testQsortUsingList = property $ do
28+
xs <- forAll $ Gen.list (Range.linear 0 1000) (Gen.int $ Range.linear 0 100)
29+
sort xs === qsortUsingList xs

test-examples/Test/Simple/Quicksort.hs

Lines changed: 0 additions & 19 deletions
This file was deleted.

test/Main.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,15 @@
33

44
module Main where
55

6-
import Test.Data.Destination (destArrayTests)
6+
import Test.Data.Array.Destination (destArrayTests)
7+
import Test.Data.Array.Mutable (mutArrTests)
8+
import Test.Data.Array.Polarized (polarizedArrayTests)
79
import Test.Data.Functor.Linear (genericTests)
8-
import Test.Data.Mutable.Array (mutArrTests)
9-
import Test.Data.Mutable.HashMap (mutHMTests)
10-
import Test.Data.Mutable.Set (mutSetTests)
11-
import Test.Data.Mutable.Vector (mutVecTests)
12-
import Test.Data.Polarized (polarizedArrayTests)
10+
import Test.Data.HashMap.Mutable (mutHMTests)
1311
import Test.Data.Replicator (replicatorInspectionTests)
12+
import Test.Data.Set.Mutable (mutSetTests)
1413
import Test.Data.V (vInspectionTests)
14+
import Test.Data.Vector.Mutable (mutVecTests)
1515
import Test.Tasty
1616

1717
main :: IO ()

test/Test/Data/Destination.hs renamed to test/Test/Data/Array/Destination.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE NoImplicitPrelude #-}
33

4-
module Test.Data.Destination (destArrayTests) where
4+
module Test.Data.Array.Destination (destArrayTests) where
55

66
import qualified Data.Array.Destination as DArray
77
import qualified Data.Vector as Vector

test/Test/Data/Mutable/Array.hs renamed to test/Test/Data/Array/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
-- Remarks:
1515
-- * We don't test for failure on out-of-bound access
1616
-- * We don't test the empty constructor because
17-
module Test.Data.Mutable.Array
17+
module Test.Data.Array.Mutable
1818
( mutArrTests,
1919
)
2020
where

test/Test/Data/Polarized.hs renamed to test/Test/Data/Array/Polarized.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE NoImplicitPrelude #-}
33

4-
module Test.Data.Polarized (polarizedArrayTests) where
4+
module Test.Data.Array.Polarized (polarizedArrayTests) where
55

66
import qualified Data.Array.Polarized as Polar
77
import qualified Data.Array.Polarized.Pull as Pull

test/Test/Data/Mutable/HashMap.hs renamed to test/Test/Data/HashMap/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@
1818
-- * We don't test alter and hope insert and delete tests suffice
1919
-- * We don't test filterWithKey and hope the test for filter suffices
2020
-- * We don't test mapMaybe since mapMaybeWithKey is more general
21-
module Test.Data.Mutable.HashMap
21+
module Test.Data.HashMap.Mutable
2222
( mutHMTests,
2323
)
2424
where

test/Test/Data/Mutable/Set.hs renamed to test/Test/Data/Set/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@
5454
-- for more about how ADT axioms work.
5555
--
5656
-- Remark: we are not testing @empty@ since it is trivial.
57-
module Test.Data.Mutable.Set
57+
module Test.Data.Set.Mutable
5858
( mutSetTests,
5959
)
6060
where

test/Test/Data/Mutable/Vector.hs renamed to test/Test/Data/Vector/Mutable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@
1515
-- Remarks:
1616
-- * We don't test for failure on out-of-bound access
1717
-- * We don't test the empty constructor
18-
module Test.Data.Mutable.Vector
18+
module Test.Data.Vector.Mutable
1919
( mutVecTests,
2020
)
2121
where

0 commit comments

Comments
 (0)