tests: custom Arbitrary OutputsSpec producing nonempty OutputsSpec_Names

This commit is contained in:
sorki 2023-12-01 19:19:28 +01:00
parent 91befa2a3c
commit 4e224c3f43
3 changed files with 16 additions and 19 deletions

View File

@ -51,6 +51,7 @@ library
base >=4.12 && <5
, hnix-store-core >= 0.8
, bytestring
, containers
, crypton
, dependent-sum > 0.7
, generic-arbitrary < 1.1
@ -80,7 +81,5 @@ test-suite props
, hnix-store-core
, hnix-store-tests
, attoparsec
, containers
, QuickCheck
, text
, hspec

View File

@ -3,13 +3,19 @@
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.DerivedPath where
import Test.QuickCheck (Arbitrary)
import qualified Data.Set
import Test.QuickCheck (Arbitrary(..), oneof)
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import System.Nix.Arbitrary.StorePath ()
import System.Nix.DerivedPath (DerivedPath, OutputsSpec)
import System.Nix.DerivedPath (DerivedPath, OutputsSpec(..))
deriving via GenericArbitrary OutputsSpec
instance Arbitrary OutputsSpec
instance Arbitrary OutputsSpec where
arbitrary = oneof
[ pure OutputsSpec_All
, OutputsSpec_Names
. Data.Set.fromList
<$> ((:) <$> arbitrary <*> arbitrary)
]
deriving via GenericArbitrary DerivedPath
instance Arbitrary DerivedPath

View File

@ -1,25 +1,17 @@
module DerivedPathSpec where
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec (Spec, describe)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Arbitrary(arbitrary), forAll, suchThat)
import Test.Hspec.Nix (roundtrips)
import System.Nix.Arbitrary ()
import System.Nix.DerivedPath (DerivedPath(..), OutputsSpec(..))
import qualified Data.Set
import qualified System.Nix.DerivedPath
spec :: Spec
spec = do
describe "DerivedPath" $ do
prop "roundtrips" $ \sd ->
forAll (arbitrary `suchThat` nonEmptyOutputsSpec_Names) $ \p ->
System.Nix.DerivedPath.parseDerivedPath sd
(System.Nix.DerivedPath.derivedPathToText sd p)
`shouldBe` pure p
where
nonEmptyOutputsSpec_Names :: DerivedPath -> Bool
nonEmptyOutputsSpec_Names (DerivedPath_Built _ (OutputsSpec_Names set)) =
not $ Data.Set.null set
nonEmptyOutputsSpec_Names _ = True
roundtrips
(System.Nix.DerivedPath.derivedPathToText sd)
(System.Nix.DerivedPath.parseDerivedPath sd)