{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.DerivedPath where
import qualified Data.Set
import Test.QuickCheck (Arbitrary(..), oneof)
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import System.Nix.Arbitrary.OutputName ()
import System.Nix.Arbitrary.StorePath ()
import System.Nix.DerivedPath (DerivedPath, OutputsSpec(..))
instance Arbitrary OutputsSpec where
arbitrary :: Gen OutputsSpec
arbitrary = [Gen OutputsSpec] -> Gen OutputsSpec
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ OutputsSpec -> Gen OutputsSpec
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OutputsSpec
OutputsSpec_All
, Set OutputName -> OutputsSpec
OutputsSpec_Names
(Set OutputName -> OutputsSpec)
-> ([OutputName] -> Set OutputName) -> [OutputName] -> OutputsSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OutputName] -> Set OutputName
forall a. Ord a => [a] -> Set a
Data.Set.fromList
([OutputName] -> OutputsSpec)
-> Gen [OutputName] -> Gen OutputsSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((:) (OutputName -> [OutputName] -> [OutputName])
-> Gen OutputName -> Gen ([OutputName] -> [OutputName])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen OutputName
forall a. Arbitrary a => Gen a
arbitrary Gen ([OutputName] -> [OutputName])
-> Gen [OutputName] -> Gen [OutputName]
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [OutputName]
forall a. Arbitrary a => Gen a
arbitrary)
]
deriving via GenericArbitrary DerivedPath
instance Arbitrary DerivedPath