Skip to content

Commit

Permalink
Change structure of examples, tests, bench, and tests-examples to pro…
Browse files Browse the repository at this point in the history
…perly match src structure
  • Loading branch information
tbagrel1 committed Sep 25, 2024
1 parent 9a7dc1b commit 9c54126
Show file tree
Hide file tree
Showing 17 changed files with 48 additions and 46 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
-- land in a file named “Array.dump-simpl”
-- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dsuppress-all -dsuppress-uniques #-}

module Data.Mutable.Array (benchmarks) where
module Bench.Data.Array.Mutable (benchmarks) where

import Control.DeepSeq (rnf)
import qualified Data.Array.Mutable.Linear as Array.Linear
Expand Down
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
{-# LANGUAGE NumericUnderscores #-}

module Data.Mutable.Quicksort (benchmarks) where
module Bench.Data.Array.Mutable.Quicksort (benchmarks) where

import Control.DeepSeq (force)
import Control.Exception (evaluate)
import Data.Array.Mutable.Quicksort (quicksortUsingArray, quicksortUsingList)
import Data.List (sort)
import Simple.Quicksort (quicksortUsingArray, quicksortUsingList)
import System.Random
import Test.Tasty.Bench

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}

module Data.Mutable.HashMap (benchmarks) where
module Bench.Data.HashMap.Mutable (benchmarks) where

import Control.DeepSeq (NFData (..), deepseq, force)
import qualified Control.Monad.Random as Random
Expand Down
10 changes: 5 additions & 5 deletions bench/Main.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
module Main where

import qualified Data.Mutable.Array as Array
import qualified Data.Mutable.HashMap as HashMap
import qualified Data.Mutable.Quicksort as Quicksort
import qualified Bench.Data.Array.Mutable as Array
import qualified Bench.Data.Array.Mutable.Quicksort as Quicksort
import qualified Bench.Data.HashMap.Mutable as HashMap
import Test.Tasty.Bench (defaultMain)

main :: IO ()
main = do
defaultMain
[ Array.benchmarks,
HashMap.benchmarks,
Quicksort.benchmarks
Quicksort.benchmarks,
HashMap.benchmarks
]
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
-- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dsuppress-all -dsuppress-uniques #-}

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

import Data.Array.Mutable.Linear (Array)
import qualified Data.Array.Mutable.Linear as Array
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}

module Simple.TopSort where
module Data.HashMap.Mutable.TopSort where

import Data.Bifunctor.Linear (second)
import qualified Data.Functor.Linear as Data
Expand Down
6 changes: 4 additions & 2 deletions examples/README.md
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
# Examples

* `Data`
* These are examples of using the pure linear interface of mutable
data structures provided by linear base.
* `Simple`
* These are tutorial level examples for understanding linear
types and using bread-and-butter tools in linear base.
* Recommended order: `Pure`, `FileIO`.
* `Foreign`
* These are examples of explicitly allocating off the GC heap's
memory and on the system heap's memory

memory and on the system heap's memory.
24 changes: 12 additions & 12 deletions linear-base.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -153,8 +153,8 @@ library examples
Foreign.Heap
Simple.FileIO
Simple.Pure
Simple.Quicksort
Simple.TopSort
Data.Array.Mutable.Quicksort
Data.HashMap.Mutable.TopSort
build-depends:
base,
linear-base,
Expand All @@ -169,12 +169,12 @@ test-suite test
main-is: Main.hs
hs-source-dirs: test
other-modules:
Test.Data.Destination
Test.Data.Mutable.Array
Test.Data.Mutable.Vector
Test.Data.Mutable.HashMap
Test.Data.Mutable.Set
Test.Data.Polarized
Test.Data.Array.Destination
Test.Data.Array.Mutable
Test.Data.Vector.Mutable
Test.Data.HashMap.Mutable
Test.Data.Set.Mutable
Test.Data.Array.Polarized
Test.Data.Functor.Linear
Test.Data.V
Test.Data.Replicator
Expand All @@ -200,7 +200,7 @@ test-suite test-examples
hs-source-dirs: test-examples
other-modules:
Test.Foreign
Test.Simple.Quicksort
Test.Data.Array.Mutable.Quicksort
default-language: Haskell2010
build-depends:
base,
Expand All @@ -217,9 +217,9 @@ benchmark bench
main-is: Main.hs
hs-source-dirs: bench
other-modules:
Data.Mutable.HashMap
Data.Mutable.Array
Data.Mutable.Quicksort
Bench.Data.HashMap.Mutable
Bench.Data.Array.Mutable
Bench.Data.Array.Mutable.Quicksort
default-language: Haskell2010
build-depends:
base,
Expand Down
2 changes: 1 addition & 1 deletion test-examples/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Main where

import Test.Data.Array.Mutable.Quicksort (quicksortTests)
import Test.Foreign (foreignGCTests)
import Test.Simple.Quicksort (quicksortTests)
import Test.Tasty

main :: IO ()
Expand Down
Original file line number Diff line number Diff line change
@@ -1,29 +1,29 @@
{-# LANGUAGE OverloadedStrings #-}

module Test.Simple.Quicksort (quicksortTests) where
module Test.Data.Array.Mutable.Quicksort (quicksortTests) where

import Data.Array.Mutable.Quicksort (quicksortUsingArray, quicksortUsingList)
import Data.List (sort)
import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Simple.Quicksort (quicksortUsingArray, quicksortUsingList)
import Test.Tasty
import Test.Tasty.Hedgehog (testPropertyNamed)

quicksortTests :: TestTree
quicksortTests =
testGroup
"quicksort tests"
[ testPropertyNamed "sort xs === quicksortUsingArray xs" "testQuicksortUsingArray" testQuicksortUsingArray,
testPropertyNamed "sort xs === quicksortUsingList xs" "testQuicksortUsingList" testQuicksortUsingList
[ testPropertyNamed "sort xs === quicksortUsingArray xs" "testQsortUsingArray" testQsortUsingArray,
testPropertyNamed "sort xs === quicksortUsingList xs" "testQsortUsingList" testQsortUsingList
]

testQuicksortUsingArray :: Property
testQuicksortUsingArray = property $ do
testQsortUsingArray :: Property
testQsortUsingArray = property $ do
xs <- forAll $ Gen.list (Range.linear 0 1000) (Gen.int $ Range.linear 0 100)
sort xs === quicksortUsingArray xs

testQuicksortUsingList :: Property
testQuicksortUsingList = property $ do
testQsortUsingList :: Property
testQsortUsingList = property $ do
xs <- forAll $ Gen.list (Range.linear 0 1000) (Gen.int $ Range.linear 0 100)
sort xs === quicksortUsingList xs
12 changes: 6 additions & 6 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,15 @@

module Main where

import Test.Data.Destination (destArrayTests)
import Test.Data.Array.Destination (destArrayTests)
import Test.Data.Array.Mutable (mutArrTests)
import Test.Data.Array.Polarized (polarizedArrayTests)
import Test.Data.Functor.Linear (genericTests)
import Test.Data.Mutable.Array (mutArrTests)
import Test.Data.Mutable.HashMap (mutHMTests)
import Test.Data.Mutable.Set (mutSetTests)
import Test.Data.Mutable.Vector (mutVecTests)
import Test.Data.Polarized (polarizedArrayTests)
import Test.Data.HashMap.Mutable (mutHMTests)
import Test.Data.Replicator (replicatorInspectionTests)
import Test.Data.Set.Mutable (mutSetTests)
import Test.Data.V (vInspectionTests)
import Test.Data.Vector.Mutable (mutVecTests)
import Test.Tasty

main :: IO ()
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Test.Data.Destination (destArrayTests) where
module Test.Data.Array.Destination (destArrayTests) where

import qualified Data.Array.Destination as DArray
import qualified Data.Vector as Vector
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
-- Remarks:
-- * We don't test for failure on out-of-bound access
-- * We don't test the empty constructor because
module Test.Data.Mutable.Array
module Test.Data.Array.Mutable
( mutArrTests,
)
where
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Test.Data.Polarized (polarizedArrayTests) where
module Test.Data.Array.Polarized (polarizedArrayTests) where

import qualified Data.Array.Polarized as Polar
import qualified Data.Array.Polarized.Pull as Pull
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
-- * We don't test alter and hope insert and delete tests suffice
-- * We don't test filterWithKey and hope the test for filter suffices
-- * We don't test mapMaybe since mapMaybeWithKey is more general
module Test.Data.Mutable.HashMap
module Test.Data.HashMap.Mutable
( mutHMTests,
)
where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@
-- for more about how ADT axioms work.
--
-- Remark: we are not testing @empty@ since it is trivial.
module Test.Data.Mutable.Set
module Test.Data.Set.Mutable
( mutSetTests,
)
where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
-- Remarks:
-- * We don't test for failure on out-of-bound access
-- * We don't test the empty constructor
module Test.Data.Mutable.Vector
module Test.Data.Vector.Mutable
( mutVecTests,
)
where
Expand Down

0 comments on commit 9c54126

Please sign in to comment.