Skip to content
Snippets Groups Projects
Commit bcb4c5f8 authored by Joachim Breitner's avatar Joachim Breitner
Browse files

Test Distribution.Client.Dependency.Modular.PSQ.splits with QuickCheck

parent 7da27034
No related merge requests found
......@@ -177,7 +177,9 @@ Test-Suite unit-tests
filepath,
test-framework,
test-framework-hunit,
test-framework-quickcheck2,
HUnit,
QuickCheck (>= 2.5),
cabal-install,
Cabal
ghc-options: -Wall
......
......@@ -4,12 +4,11 @@ module UnitTests.Distribution.Client.Dependency.Modular.PSQ (
import Distribution.Client.Dependency.Modular.PSQ
import Test.Framework as TF (Test)
import Test.Framework.Providers.HUnit (testCase)
import Test.HUnit (Assertion, assertEqual)
import Test.Framework as TF (Test)
import Test.Framework.Providers.QuickCheck2
tests :: [TF.Test]
tests = [ testCase "splitsAltImplementation" splitsTest
tests = [ testProperty "splitsAltImplementation" splitsTest
]
-- | Original splits implementation
......@@ -19,12 +18,5 @@ splits' xs =
(PSQ [])
(\ k v ys -> cons k (v, ys) (fmap (\ (w, zs) -> (w, cons k v zs)) (splits' ys)))
splitsTest :: Assertion
splitsTest = do
assertEqual "" (splits' psq1) (splits psq1)
assertEqual "" (splits' psq2) (splits psq2)
assertEqual "" (splits' psq3) (splits psq3)
where
psq1 = PSQ [ (1,2), (3,4), (5,6), (7,8) ] :: PSQ Int Int
psq2 = PSQ [ (1,2) ] :: PSQ Int Int
psq3 = PSQ [] :: PSQ Int Int
splitsTest :: [(Int, Int)] -> Bool
splitsTest psq = splits' (PSQ psq) == splits (PSQ psq)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment