11{-# LANGUAGE AllowAmbiguousTypes #-}
2- {-# LANGUAGE CPP #-}
32{-# LANGUAGE DeriveAnyClass #-}
43{-# LANGUAGE OverloadedStrings #-}
54{-|
@@ -32,19 +31,15 @@ module System.Nix.StorePath
3231 , pathParser
3332 ) where
3433
35- #if !MIN_VERSION_base(4,18,0)
36- import Control.Applicative (liftA2 )
37- #endif
3834import Control.Monad.Reader.Class (MonadReader , asks )
39- import Crypto.Hash (HashAlgorithm , SHA256 )
35+ import Crypto.Hash (HashAlgorithm )
4036import Data.Attoparsec.Text.Lazy (Parser , (<?>) )
4137import Data.ByteString (ByteString )
4238import Data.Default.Class (Default (def ))
4339import Data.Hashable (Hashable (hashWithSalt ))
4440import Data.Text (Text )
4541import GHC.Generics (Generic )
4642import System.Nix.Base (BaseEncoding (NixBase32 ))
47- import Test.QuickCheck (Arbitrary (arbitrary ), listOf , elements )
4843
4944import qualified Data.Bifunctor
5045import qualified Data.ByteString.Char8
@@ -81,12 +76,6 @@ instance Hashable StorePath where
8176 hashWithSalt s StorePath {.. } =
8277 s `hashWithSalt` storePathHash `hashWithSalt` storePathName
8378
84- instance Arbitrary StorePath where
85- arbitrary =
86- liftA2 StorePath
87- arbitrary
88- arbitrary
89-
9079-- | The name portion of a Nix path.
9180--
9281-- 'unStorePathName' must only contain a-zA-Z0-9+._?=-, can't start
@@ -97,25 +86,13 @@ newtype StorePathName = StorePathName
9786 unStorePathName :: Text
9887 } deriving (Eq , Generic , Hashable , Ord , Show )
9988
100- instance Arbitrary StorePathName where
101- arbitrary = StorePathName . Data.Text. pack <$> ((:) <$> s1 <*> listOf sn)
102- where
103- alphanum = [' a' .. ' z' ] <> [' A' .. ' Z' ] <> [' 0' .. ' 9' ]
104- s1 = elements $ alphanum <> " +-_?="
105- sn = elements $ alphanum <> " +-._?="
106-
10789-- | The hash algorithm used for store path hashes.
10890newtype StorePathHashPart = StorePathHashPart
10991 { -- | Extract the contents of the hash.
11092 unStorePathHashPart :: ByteString
11193 }
11294 deriving (Eq , Generic , Hashable , Ord , Show )
11395
114- instance Arbitrary StorePathHashPart where
115- arbitrary =
116- mkStorePathHashPart @ SHA256
117- . Data.ByteString.Char8. pack <$> arbitrary
118-
11996-- | Make @StorePathHashPart@ from @ByteString@ (hash part of the @StorePath@)
12097-- using specific @HashAlgorithm@
12198mkStorePathHashPart
@@ -183,12 +160,6 @@ newtype StoreDir = StoreDir {
183160 unStoreDir :: RawFilePath
184161 } deriving (Eq , Generic , Hashable , Ord , Show )
185162
186- instance Arbitrary StoreDir where
187- arbitrary =
188- StoreDir
189- . (" /" <> ) -- TODO(srk): nasty, see #237
190- . Data.ByteString.Char8. pack <$> arbitrary
191-
192163instance Default StoreDir where
193164 def = StoreDir " /nix/store"
194165
0 commit comments