From e7622b326979caf1526aecab7f0ea648905c5eb2 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 11:00:52 +0100 Subject: [PATCH 01/13] remote: move default-extensions into common stanza --- hnix-store-remote/hnix-store-remote.cabal | 57 ++++++++--------------- 1 file changed, 19 insertions(+), 38 deletions(-) diff --git a/hnix-store-remote/hnix-store-remote.cabal b/hnix-store-remote/hnix-store-remote.cabal index 7cddf75..2153268 100644 --- a/hnix-store-remote/hnix-store-remote.cabal +++ b/hnix-store-remote/hnix-store-remote.cabal @@ -18,6 +18,25 @@ Common commons ghc-options: -Wall -Wunused-packages else ghc-options: -Wall + default-extensions: + OverloadedStrings + , DeriveGeneric + , DeriveDataTypeable + , DeriveFunctor + , DeriveFoldable + , DeriveTraversable + , DeriveLift + , FlexibleContexts + , FlexibleInstances + , StandaloneDeriving + , TypeApplications + , TypeSynonymInstances + , InstanceSigs + , MultiParamTypeClasses + , TupleSections + , LambdaCase + , BangPatterns + , ViewPatterns flag io-testsuite default: @@ -64,25 +83,6 @@ library base hiding (Prelude) , relude (Relude as Prelude) , relude - default-extensions: - OverloadedStrings - , DeriveGeneric - , DeriveDataTypeable - , DeriveFunctor - , DeriveFoldable - , DeriveTraversable - , DeriveLift - , FlexibleContexts - , FlexibleInstances - , StandaloneDeriving - , TypeApplications - , TypeSynonymInstances - , InstanceSigs - , MultiParamTypeClasses - , TupleSections - , LambdaCase - , BangPatterns - , ViewPatterns hs-source-dirs: src default-language: Haskell2010 ghc-options: -Wall @@ -139,23 +139,4 @@ test-suite hnix-store-remote-tests base hiding (Prelude) , relude (Relude as Prelude) , relude - default-extensions: - OverloadedStrings - , DeriveGeneric - , DeriveDataTypeable - , DeriveFunctor - , DeriveFoldable - , DeriveTraversable - , DeriveLift - , FlexibleContexts - , FlexibleInstances - , StandaloneDeriving - , TypeApplications - , TypeSynonymInstances - , InstanceSigs - , MultiParamTypeClasses - , TupleSections - , LambdaCase - , BangPatterns - , ViewPatterns default-language: Haskell2010 From b1e590606e823e1a6cd3e561f34cebe8e4a31d26 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 11:50:05 +0100 Subject: [PATCH 02/13] core: don't (re)export StorePathName constructor --- hnix-store-core/src/System/Nix/ReadonlyStore.hs | 2 +- hnix-store-core/src/System/Nix/StorePath.hs | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/hnix-store-core/src/System/Nix/ReadonlyStore.hs b/hnix-store-core/src/System/Nix/ReadonlyStore.hs index 52a1cec..acca377 100644 --- a/hnix-store-core/src/System/Nix/ReadonlyStore.hs +++ b/hnix-store-core/src/System/Nix/ReadonlyStore.hs @@ -38,7 +38,7 @@ makeStorePath storeDir ty h nm = StorePath (coerce storeHash) nm [ algoName @h , encodeDigestWith Base16 h , toText . Bytes.Char8.unpack $ unStoreDir storeDir - , coerce nm + , unStorePathName nm ] makeTextPath diff --git a/hnix-store-core/src/System/Nix/StorePath.hs b/hnix-store-core/src/System/Nix/StorePath.hs index c87c65d..2932cb8 100644 --- a/hnix-store-core/src/System/Nix/StorePath.hs +++ b/hnix-store-core/src/System/Nix/StorePath.hs @@ -5,7 +5,7 @@ module System.Nix.StorePath ( -- * Basic store path types StoreDir(..) , StorePath(..) - , StorePathName(..) + , StorePathName , StorePathSet , mkStorePathHashPart , StorePathHashPart(..) @@ -13,6 +13,7 @@ module System.Nix.StorePath , NarHashMode(..) , -- * Manipulating 'StorePathName' makeStorePathName + , unStorePathName , validStorePathName , -- * Rendering out 'StorePath's storePathToFilePath From c095d1242778903a6e1684d5b0e6d82cd9dc6f4c Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 12:32:25 +0100 Subject: [PATCH 03/13] remote: move flags to Types, wrap in newtype --- hnix-store-remote/README.md | 2 +- .../src/System/Nix/Store/Remote.hs | 17 +++++---- .../src/System/Nix/Store/Remote/Types.hs | 37 +++++++++++++++++++ hnix-store-remote/tests/NixDaemon.hs | 14 +++---- 4 files changed, 54 insertions(+), 16 deletions(-) diff --git a/hnix-store-remote/README.md b/hnix-store-remote/README.md index e2cc777..a8c7135 100644 --- a/hnix-store-remote/README.md +++ b/hnix-store-remote/README.md @@ -25,6 +25,6 @@ main = do roots <- findRoots liftIO $ print roots - res <- addTextToStore "hnix-store" "test" mempty False + res <- addTextToStore "hnix-store" "test" mempty dontRepair liftIO $ print res ``` diff --git a/hnix-store-remote/src/System/Nix/Store/Remote.hs b/hnix-store-remote/src/System/Nix/Store/Remote.hs index 0231477..0cdcbdb 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote.hs @@ -71,9 +71,6 @@ import System.Nix.Store.Remote.Util import Crypto.Hash ( SHA256 ) import System.Nix.Nar ( NarSource ) -type RepairFlag = Bool -type CheckFlag = Bool -type SubstituteFlag = Bool -- | Pack `Nar` and add it to the store. addToStore @@ -84,7 +81,10 @@ addToStore -> Bool -- ^ Add target directory recursively -> RepairFlag -- ^ Only used by local store backend -> MonadStore StorePath -addToStore name source recursive _repair = do +addToStore name source recursive repair = do + when (unRepairFlag repair) + $ error "repairing is not supported when building through the Nix daemon" + runOpArgsIO AddToStore $ \yield -> do yield $ toStrict $ Data.Binary.Put.runPut $ do putText $ System.Nix.StorePath.unStorePathName name @@ -105,8 +105,9 @@ addTextToStore -> RepairFlag -- ^ Repair flag, must be `False` in case of remote backend -> MonadStore StorePath addTextToStore name text references' repair = do - when repair + when (unRepairFlag repair) $ error "repairing is not supported when building through the Nix daemon" + storeDir <- getStoreDir runOpArgs AddTextToStore $ do putText name @@ -204,7 +205,7 @@ queryValidPaths ps substitute = do storeDir <- getStoreDir runOpArgs QueryValidPaths $ do putPaths storeDir ps - putBool substitute + putBool (unSubstituteFlag substitute) sockGetPaths queryAllValidPaths :: MonadStore StorePathSet @@ -321,5 +322,5 @@ syncWithGC = void $ simpleOp SyncWithGC -- returns True on errors verifyStore :: CheckFlag -> RepairFlag -> MonadStore Bool verifyStore check repair = simpleOpArgs VerifyStore $ do - putBool check - putBool repair + putBool $ unCheckFlag check + putBool $ unRepairFlag repair diff --git a/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs b/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs index 9150059..25b50dc 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs @@ -4,6 +4,18 @@ module System.Nix.Store.Remote.Types ( MonadStore , StoreConfig(..) + , CheckFlag + , doCheck + , dontCheck + , unCheckFlag + , RepairFlag + , doRepair + , dontRepair + , unRepairFlag + , SubstituteFlag + , doSubstitute + , dontSubstitute + , unSubstituteFlag , Logger(..) , Field(..) , mapStoreDir @@ -29,6 +41,31 @@ data StoreConfig = StoreConfig , storeSocket :: Socket } +-- | Check flag, used by @verifyStore@ +newtype CheckFlag = CheckFlag { unCheckFlag :: Bool } + deriving (Eq, Ord, Show) + +doCheck, dontCheck :: CheckFlag +doCheck = CheckFlag True +dontCheck = CheckFlag False + +-- | Repair flag, used by @addToStore@, @addTextToStore@ +-- and @verifyStore@ +newtype RepairFlag = RepairFlag { unRepairFlag :: Bool } + deriving (Eq, Ord, Show) + +doRepair, dontRepair :: RepairFlag +doRepair = RepairFlag True +dontRepair = RepairFlag False + +-- | Substitute flag, used by @queryValidPaths@ +newtype SubstituteFlag = SubstituteFlag { unSubstituteFlag :: Bool } + deriving (Eq, Ord, Show) + +doSubstitute, dontSubstitute :: SubstituteFlag +doSubstitute = SubstituteFlag True +dontSubstitute = SubstituteFlag False + type MonadStore a = ExceptT String diff --git a/hnix-store-remote/tests/NixDaemon.hs b/hnix-store-remote/tests/NixDaemon.hs index c3afbbb..fae3579 100644 --- a/hnix-store-remote/tests/NixDaemon.hs +++ b/hnix-store-remote/tests/NixDaemon.hs @@ -154,14 +154,14 @@ itLefts name action = it name action isLeft withPath :: (StorePath -> MonadStore a) -> MonadStore a withPath action = do - path <- addTextToStore "hnix-store" "test" (HS.fromList []) False + path <- addTextToStore "hnix-store" "test" mempty dontRepair action path -- | dummy path, adds /dummpy with "Hello World" contents dummy :: MonadStore StorePath dummy = do let name = Data.Either.fromRight (error "impossible") $ makeStorePathName "dummy" - addToStore @SHA256 name (dumpPath "dummy") False False + addToStore @SHA256 name (dumpPath "dummy") False dontRepair invalidPath :: StorePath invalidPath = @@ -170,7 +170,7 @@ invalidPath = withBuilder :: (StorePath -> MonadStore a) -> MonadStore a withBuilder action = do - path <- addTextToStore "builder" builderSh (HS.fromList []) False + path <- addTextToStore "builder" builderSh mempty dontRepair action path builderSh :: Text @@ -186,14 +186,14 @@ spec_protocol = Hspec.around withNixDaemon $ context "verifyStore" $ do itRights "check=False repair=False" $ - verifyStore False False `shouldReturn` False + verifyStore dontCheck dontRepair `shouldReturn` False itRights "check=True repair=False" $ - verifyStore True False `shouldReturn` False + verifyStore doCheck dontRepair `shouldReturn` False --privileged itRights "check=True repair=True" $ - verifyStore True True `shouldReturn` False + verifyStore doCheck doRepair `shouldReturn` False context "addTextToStore" $ itRights "adds text to store" $ withPath pure @@ -252,7 +252,7 @@ spec_protocol = Hspec.around withNixDaemon $ itRights "adds file to store" $ do fp <- liftIO $ writeSystemTempFile "addition" "lal" let name = Data.Either.fromRight (error "impossible") $ makeStorePathName "tmp-addition" - res <- addToStore @SHA256 name (dumpPath fp) False False + res <- addToStore @SHA256 name (dumpPath fp) False dontRepair liftIO $ print res context "with dummy" $ do From 3b3752d758f16b7ed1fb0474a65eb52c76a9436a Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 12:35:38 +0100 Subject: [PATCH 04/13] core: don't (re)export StorePathHashPart constructor --- .../src/System/Nix/Internal/StorePath.hs | 16 ++++++++++++---- hnix-store-core/src/System/Nix/ReadonlyStore.hs | 12 ++++++------ hnix-store-core/src/System/Nix/StorePath.hs | 3 ++- hnix-store-core/tests/Arbitrary.hs | 2 +- hnix-store-core/tests/Hash.hs | 5 +++-- hnix-store-remote/src/System/Nix/Store/Remote.hs | 5 ++++- hnix-store-remote/tests/NixDaemon.hs | 2 +- 7 files changed, 29 insertions(+), 16 deletions(-) diff --git a/hnix-store-core/src/System/Nix/Internal/StorePath.hs b/hnix-store-core/src/System/Nix/Internal/StorePath.hs index e307098..8d6d820 100644 --- a/hnix-store-core/src/System/Nix/Internal/StorePath.hs +++ b/hnix-store-core/src/System/Nix/Internal/StorePath.hs @@ -14,8 +14,8 @@ module System.Nix.Internal.StorePath , StorePath(..) , StorePathName(..) , StorePathSet - , mkStorePathHashPart , StorePathHashPart(..) + , mkStorePathHashPart , ContentAddressableAddress(..) , NarHashMode(..) , -- * Manipulating 'StorePathName' @@ -47,6 +47,7 @@ import qualified Data.Attoparsec.Text.Lazy as Parser.Text.Lazy import qualified System.FilePath as FilePath import Crypto.Hash ( SHA256 , Digest + , HashAlgorithm ) -- | A path in a Nix store. @@ -83,11 +84,18 @@ newtype StorePathName = StorePathName } deriving (Eq, Hashable, Ord, Show) -- | The hash algorithm used for store path hashes. -newtype StorePathHashPart = StorePathHashPart ByteString +newtype StorePathHashPart = StorePathHashPart + { -- | Extract the contents of the hash. + unStorePathHashPart :: ByteString + } deriving (Eq, Hashable, Ord, Show) -mkStorePathHashPart :: ByteString -> StorePathHashPart -mkStorePathHashPart = coerce . mkStorePathHash @SHA256 +mkStorePathHashPart + :: forall hashAlgo + . HashAlgorithm hashAlgo + => ByteString + -> StorePathHashPart +mkStorePathHashPart = coerce . mkStorePathHash @hashAlgo -- | A set of 'StorePath's. type StorePathSet = HashSet StorePath diff --git a/hnix-store-core/src/System/Nix/ReadonlyStore.hs b/hnix-store-core/src/System/Nix/ReadonlyStore.hs index acca377..e95a19d 100644 --- a/hnix-store-core/src/System/Nix/ReadonlyStore.hs +++ b/hnix-store-core/src/System/Nix/ReadonlyStore.hs @@ -22,20 +22,20 @@ import Crypto.Hash ( Context makeStorePath - :: forall h - . (NamedAlgo h) + :: forall hashAlgo + . (NamedAlgo hashAlgo) => StoreDir -> ByteString - -> Digest h + -> Digest hashAlgo -> StorePathName -> StorePath -makeStorePath storeDir ty h nm = StorePath (coerce storeHash) nm +makeStorePath storeDir ty h nm = StorePath storeHash nm where - storeHash = mkStorePathHash @h s + storeHash = mkStorePathHashPart @hashAlgo s s = BS.intercalate ":" $ ty:fmap encodeUtf8 - [ algoName @h + [ algoName @hashAlgo , encodeDigestWith Base16 h , toText . Bytes.Char8.unpack $ unStoreDir storeDir , unStorePathName nm diff --git a/hnix-store-core/src/System/Nix/StorePath.hs b/hnix-store-core/src/System/Nix/StorePath.hs index 2932cb8..b414d10 100644 --- a/hnix-store-core/src/System/Nix/StorePath.hs +++ b/hnix-store-core/src/System/Nix/StorePath.hs @@ -7,8 +7,9 @@ module System.Nix.StorePath , StorePath(..) , StorePathName , StorePathSet + , StorePathHashPart , mkStorePathHashPart - , StorePathHashPart(..) + , unStorePathHashPart , ContentAddressableAddress(..) , NarHashMode(..) , -- * Manipulating 'StorePathName' diff --git a/hnix-store-core/tests/Arbitrary.hs b/hnix-store-core/tests/Arbitrary.hs index 3a12f44..dcf40aa 100644 --- a/hnix-store-core/tests/Arbitrary.hs +++ b/hnix-store-core/tests/Arbitrary.hs @@ -30,7 +30,7 @@ instance Arbitrary StorePathName where sn = elements $ alphanum <> "+-._?=" instance Arbitrary StorePathHashPart where - arbitrary = mkStorePathHashPart . BSC.pack <$> arbitrary + arbitrary = mkStorePathHashPart @SHA256 . BSC.pack <$> arbitrary instance Arbitrary (Digest SHA256) where arbitrary = hash . BSC.pack <$> arbitrary diff --git a/hnix-store-core/tests/Hash.hs b/hnix-store-core/tests/Hash.hs index 690f3d5..9a78342 100644 --- a/hnix-store-core/tests/Hash.hs +++ b/hnix-store-core/tests/Hash.hs @@ -37,7 +37,7 @@ spec_hash = do -- The example in question: -- https://nixos.org/nixos/nix-pills/nix-store-paths.html it "produces same base32 as nix pill flat file example" $ do - shouldBe (encodeWith NixBase32 $ coerce $ mkStorePathHashPart "source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3c0d7b98883f9ee3:/nix/store:myfile") + shouldBe (encodeWith NixBase32 $ unStorePathHashPart $ mkStorePathHashPart @SHA256 "source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3c0d7b98883f9ee3:/nix/store:myfile") "xv2iccirbrvklck36f1g7vldn5v58vck" where cmp :: String -> BaseEncoding -> (ByteString -> Digest a) -> ByteString -> Text -> SpecWith () @@ -52,7 +52,8 @@ prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $ -- | API variants prop_nixBase16Roundtrip :: StorePathHashPart -> Property -prop_nixBase16Roundtrip x = pure (coerce x) === decodeWith Base16 (encodeWith Base16 $ coerce x) +prop_nixBase16Roundtrip x = + pure (unStorePathHashPart x) === decodeWith Base16 (encodeWith Base16 $ unStorePathHashPart x) -- | Hash encoding conversion ground-truth. -- Similiar to nix/tests/hash.sh diff --git a/hnix-store-remote/src/System/Nix/Store/Remote.hs b/hnix-store-remote/src/System/Nix/Store/Remote.hs index 0cdcbdb..a2f18c5 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote.hs @@ -290,7 +290,10 @@ queryPathFromHashPart :: StorePathHashPart -> MonadStore StorePath queryPathFromHashPart storePathHash = do runOpArgs QueryPathFromHashPart $ putByteStringLen - $ encodeUtf8 (encodeWith NixBase32 $ coerce storePathHash) + $ encodeUtf8 + $ encodeWith NixBase32 + $ System.Nix.StorePath.unStorePathHashPart + storePathHash sockGetPath queryMissing diff --git a/hnix-store-remote/tests/NixDaemon.hs b/hnix-store-remote/tests/NixDaemon.hs index fae3579..60781c4 100644 --- a/hnix-store-remote/tests/NixDaemon.hs +++ b/hnix-store-remote/tests/NixDaemon.hs @@ -166,7 +166,7 @@ dummy = do invalidPath :: StorePath invalidPath = let name = Data.Either.fromRight (error "impossible") $ makeStorePathName "invalid" - in StorePath (mkStorePathHashPart "invalid") name + in StorePath (mkStorePathHashPart @SHA256 "invalid") name withBuilder :: (StorePath -> MonadStore a) -> MonadStore a withBuilder action = do From 6f21bb30ef90b39174b83eaa142997af66a366ae Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 12:43:42 +0100 Subject: [PATCH 05/13] remote: add Recursive newtype for addToStore --- hnix-store-remote/src/System/Nix/Store/Remote.hs | 6 +++--- .../src/System/Nix/Store/Remote/Types.hs | 14 ++++++++++++++ hnix-store-remote/tests/NixDaemon.hs | 4 ++-- 3 files changed, 19 insertions(+), 5 deletions(-) diff --git a/hnix-store-remote/src/System/Nix/Store/Remote.hs b/hnix-store-remote/src/System/Nix/Store/Remote.hs index a2f18c5..5df9153 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote.hs @@ -78,7 +78,7 @@ addToStore . (NamedAlgo a) => StorePathName -- ^ Name part of the newly created `StorePath` -> NarSource MonadStore -- ^ provide nar stream - -> Bool -- ^ Add target directory recursively + -> Recursive -- ^ Add target directory recursively -> RepairFlag -- ^ Only used by local store backend -> MonadStore StorePath addToStore name source recursive repair = do @@ -88,8 +88,8 @@ addToStore name source recursive repair = do runOpArgsIO AddToStore $ \yield -> do yield $ toStrict $ Data.Binary.Put.runPut $ do putText $ System.Nix.StorePath.unStorePathName name - putBool $ not $ System.Nix.Hash.algoName @a == "sha256" && recursive - putBool recursive + putBool $ not $ System.Nix.Hash.algoName @a == "sha256" && (unRecursive recursive) + putBool (unRecursive recursive) putText $ System.Nix.Hash.algoName @a source yield sockGetPath diff --git a/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs b/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs index 25b50dc..b3cda6a 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote/Types.hs @@ -16,6 +16,10 @@ module System.Nix.Store.Remote.Types , doSubstitute , dontSubstitute , unSubstituteFlag + , Recursive + , addRecursive + , addNonRecursive + , unRecursive , Logger(..) , Field(..) , mapStoreDir @@ -66,6 +70,16 @@ doSubstitute, dontSubstitute :: SubstituteFlag doSubstitute = SubstituteFlag True dontSubstitute = SubstituteFlag False +-- | Recursive, used by @addToStore@ +newtype Recursive = Recursive { unRecursive :: Bool } + deriving (Eq, Ord, Show) + +addRecursive, addNonRecursive :: Recursive +-- | Add target directory recursively +addRecursive = Recursive True +-- | Add target directory non-recursively +addNonRecursive = Recursive False + type MonadStore a = ExceptT String diff --git a/hnix-store-remote/tests/NixDaemon.hs b/hnix-store-remote/tests/NixDaemon.hs index 60781c4..94cf45d 100644 --- a/hnix-store-remote/tests/NixDaemon.hs +++ b/hnix-store-remote/tests/NixDaemon.hs @@ -161,7 +161,7 @@ withPath action = do dummy :: MonadStore StorePath dummy = do let name = Data.Either.fromRight (error "impossible") $ makeStorePathName "dummy" - addToStore @SHA256 name (dumpPath "dummy") False dontRepair + addToStore @SHA256 name (dumpPath "dummy") addNonRecursive dontRepair invalidPath :: StorePath invalidPath = @@ -252,7 +252,7 @@ spec_protocol = Hspec.around withNixDaemon $ itRights "adds file to store" $ do fp <- liftIO $ writeSystemTempFile "addition" "lal" let name = Data.Either.fromRight (error "impossible") $ makeStorePathName "tmp-addition" - res <- addToStore @SHA256 name (dumpPath fp) False dontRepair + res <- addToStore @SHA256 name (dumpPath fp) addNonRecursive dontRepair liftIO $ print res context "with dummy" $ do From fe33fba30b7154d68c0299df2c7ba4c99971f385 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 12:53:26 +0100 Subject: [PATCH 06/13] Drop StorePathSet type alias --- .../src/System/Nix/Internal/StorePath.hs | 4 -- .../src/System/Nix/ReadonlyStore.hs | 4 +- hnix-store-core/src/System/Nix/StorePath.hs | 1 - .../src/System/Nix/StorePathMetadata.hs | 3 +- .../src/System/Nix/Store/Remote.hs | 39 +++++++++---------- .../src/System/Nix/Store/Remote/Util.hs | 6 +-- 6 files changed, 25 insertions(+), 32 deletions(-) diff --git a/hnix-store-core/src/System/Nix/Internal/StorePath.hs b/hnix-store-core/src/System/Nix/Internal/StorePath.hs index 8d6d820..4ded6ad 100644 --- a/hnix-store-core/src/System/Nix/Internal/StorePath.hs +++ b/hnix-store-core/src/System/Nix/Internal/StorePath.hs @@ -13,7 +13,6 @@ module System.Nix.Internal.StorePath StoreDir(..) , StorePath(..) , StorePathName(..) - , StorePathSet , StorePathHashPart(..) , mkStorePathHashPart , ContentAddressableAddress(..) @@ -97,9 +96,6 @@ mkStorePathHashPart -> StorePathHashPart mkStorePathHashPart = coerce . mkStorePathHash @hashAlgo --- | A set of 'StorePath's. -type StorePathSet = HashSet StorePath - -- | An address for a content-addressable store path, i.e. one whose -- store path hash is purely a function of its contents (as opposed to -- paths that are derivation outputs, whose hashes are a function of diff --git a/hnix-store-core/src/System/Nix/ReadonlyStore.hs b/hnix-store-core/src/System/Nix/ReadonlyStore.hs index e95a19d..f299a6c 100644 --- a/hnix-store-core/src/System/Nix/ReadonlyStore.hs +++ b/hnix-store-core/src/System/Nix/ReadonlyStore.hs @@ -42,7 +42,7 @@ makeStorePath storeDir ty h nm = StorePath storeHash nm ] makeTextPath - :: StoreDir -> StorePathName -> Digest SHA256 -> StorePathSet -> StorePath + :: StoreDir -> StorePathName -> Digest SHA256 -> HashSet StorePath -> StorePath makeTextPath storeDir nm h refs = makeStorePath storeDir ty h nm where ty = @@ -70,7 +70,7 @@ makeFixedOutputPath storeDir recursive h = <> ":" computeStorePathForText - :: StoreDir -> StorePathName -> ByteString -> (StorePathSet -> StorePath) + :: StoreDir -> StorePathName -> ByteString -> (HashSet StorePath -> StorePath) computeStorePathForText storeDir nm = makeTextPath storeDir nm . hash computeStorePathForPath diff --git a/hnix-store-core/src/System/Nix/StorePath.hs b/hnix-store-core/src/System/Nix/StorePath.hs index b414d10..d30450f 100644 --- a/hnix-store-core/src/System/Nix/StorePath.hs +++ b/hnix-store-core/src/System/Nix/StorePath.hs @@ -6,7 +6,6 @@ module System.Nix.StorePath StoreDir(..) , StorePath(..) , StorePathName - , StorePathSet , StorePathHashPart , mkStorePathHashPart , unStorePathHashPart diff --git a/hnix-store-core/src/System/Nix/StorePathMetadata.hs b/hnix-store-core/src/System/Nix/StorePathMetadata.hs index 49b3bd8..926ddaf 100644 --- a/hnix-store-core/src/System/Nix/StorePathMetadata.hs +++ b/hnix-store-core/src/System/Nix/StorePathMetadata.hs @@ -4,7 +4,6 @@ Description : Metadata about Nix store paths. module System.Nix.StorePathMetadata where import System.Nix.StorePath ( StorePath - , StorePathSet , ContentAddressableAddress ) import System.Nix.Hash ( SomeNamedDigest ) @@ -22,7 +21,7 @@ data StorePathMetadata = StorePathMetadata -- | The hash of the nar serialization of the path. narHash :: !SomeNamedDigest , -- | The paths that this path directly references - references :: !StorePathSet + references :: !(HashSet StorePath) , -- | When was this path registered valid in the store? registrationTime :: !UTCTime , -- | The size of the nar serialization of the path, in bytes. diff --git a/hnix-store-remote/src/System/Nix/Store/Remote.hs b/hnix-store-remote/src/System/Nix/Store/Remote.hs index 5df9153..cafe0e1 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote.hs @@ -49,7 +49,6 @@ import System.Nix.Hash ( NamedAlgo(..) ) import System.Nix.StorePath ( StorePath , StorePathName - , StorePathSet , StorePathHashPart ) import System.Nix.StorePathMetadata ( StorePathMetadata(..) @@ -99,10 +98,10 @@ addToStore name source recursive repair = do -- Reference accepts repair but only uses it -- to throw error in case of remote talking to nix-daemon. addTextToStore - :: Text -- ^ Name of the text - -> Text -- ^ Actual text to add - -> StorePathSet -- ^ Set of `StorePath`s that the added text references - -> RepairFlag -- ^ Repair flag, must be `False` in case of remote backend + :: Text -- ^ Name of the text + -> Text -- ^ Actual text to add + -> HashSet StorePath -- ^ Set of `StorePath`s that the added text references + -> RepairFlag -- ^ Repair flag, must be `False` in case of remote backend -> MonadStore StorePath addTextToStore name text references' repair = do when (unRepairFlag repair) @@ -138,7 +137,7 @@ addTempRoot pn = do -- | Build paths if they are an actual derivations. -- -- If derivation output paths are already valid, do nothing. -buildPaths :: StorePathSet -> BuildMode -> MonadStore () +buildPaths :: HashSet StorePath -> BuildMode -> MonadStore () buildPaths ps bm = do storeDir <- getStoreDir void $ simpleOpArgs BuildPaths $ do @@ -198,9 +197,9 @@ isValidPathUncached p = do -- | Query valid paths from set, optionally try to use substitutes. queryValidPaths - :: StorePathSet -- ^ Set of `StorePath`s to query + :: HashSet StorePath -- ^ Set of `StorePath`s to query -> SubstituteFlag -- ^ Try substituting missing paths when `True` - -> MonadStore StorePathSet + -> MonadStore (HashSet StorePath) queryValidPaths ps substitute = do storeDir <- getStoreDir runOpArgs QueryValidPaths $ do @@ -208,12 +207,12 @@ queryValidPaths ps substitute = do putBool (unSubstituteFlag substitute) sockGetPaths -queryAllValidPaths :: MonadStore StorePathSet +queryAllValidPaths :: MonadStore (HashSet StorePath) queryAllValidPaths = do runOp QueryAllValidPaths sockGetPaths -querySubstitutablePaths :: StorePathSet -> MonadStore StorePathSet +querySubstitutablePaths :: HashSet StorePath -> MonadStore (HashSet StorePath) querySubstitutablePaths ps = do storeDir <- getStoreDir runOpArgs QuerySubstitutablePaths $ putPaths storeDir ps @@ -262,25 +261,25 @@ queryPathInfoUncached path = do pure $ StorePathMetadata{..} -queryReferrers :: StorePath -> MonadStore StorePathSet +queryReferrers :: StorePath -> MonadStore (HashSet StorePath) queryReferrers p = do storeDir <- getStoreDir runOpArgs QueryReferrers $ putPath storeDir p sockGetPaths -queryValidDerivers :: StorePath -> MonadStore StorePathSet +queryValidDerivers :: StorePath -> MonadStore (HashSet StorePath) queryValidDerivers p = do storeDir <- getStoreDir runOpArgs QueryValidDerivers $ putPath storeDir p sockGetPaths -queryDerivationOutputs :: StorePath -> MonadStore StorePathSet +queryDerivationOutputs :: StorePath -> MonadStore (HashSet StorePath) queryDerivationOutputs p = do storeDir <- getStoreDir runOpArgs QueryDerivationOutputs $ putPath storeDir p sockGetPaths -queryDerivationOutputNames :: StorePath -> MonadStore StorePathSet +queryDerivationOutputNames :: StorePath -> MonadStore (HashSet StorePath) queryDerivationOutputNames p = do storeDir <- getStoreDir runOpArgs QueryDerivationOutputNames $ putPath storeDir p @@ -297,13 +296,13 @@ queryPathFromHashPart storePathHash = do sockGetPath queryMissing - :: StorePathSet + :: (HashSet StorePath) -> MonadStore - ( StorePathSet-- Paths that will be built - , StorePathSet -- Paths that have substitutes - , StorePathSet -- Unknown paths - , Integer -- Download size - , Integer -- Nar size? + ( HashSet StorePath -- Paths that will be built + , HashSet StorePath -- Paths that have substitutes + , HashSet StorePath -- Unknown paths + , Integer -- Download size + , Integer -- Nar size? ) queryMissing ps = do storeDir <- getStoreDir diff --git a/hnix-store-remote/src/System/Nix/Store/Remote/Util.hs b/hnix-store-remote/src/System/Nix/Store/Remote/Util.hs index 6b576c8..8692a1c 100644 --- a/hnix-store-remote/src/System/Nix/Store/Remote/Util.hs +++ b/hnix-store-remote/src/System/Nix/Store/Remote/Util.hs @@ -83,7 +83,7 @@ sockGetPathMay = do Just pth -sockGetPaths :: MonadStore StorePathSet +sockGetPaths :: MonadStore (HashSet StorePath) sockGetPaths = do sd <- getStoreDir getSocketIncremental (getPaths sd) @@ -109,14 +109,14 @@ putTexts = putByteStrings . fmap textToBSL getPath :: StoreDir -> Get (Either String StorePath) getPath sd = parsePath sd <$> getByteStringLen -getPaths :: StoreDir -> Get StorePathSet +getPaths :: StoreDir -> Get (HashSet StorePath) getPaths sd = Data.HashSet.fromList . rights . fmap (parsePath sd) <$> getByteStrings putPath :: StoreDir -> StorePath -> Put putPath storeDir = putByteStringLen . fromStrict . storePathToRawFilePath storeDir -putPaths :: StoreDir -> StorePathSet -> Put +putPaths :: StoreDir -> HashSet StorePath -> Put putPaths storeDir = putByteStrings . Data.HashSet.toList . Data.HashSet.map (fromStrict . storePathToRawFilePath storeDir) From b98fb44d7fb97729bed0980856f9c9c93dd5b8c2 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 16:38:19 +0100 Subject: [PATCH 07/13] remote: rename testsuite to remote-io, move to tests-io --- hnix-store-remote/hnix-store-remote.cabal | 9 ++++----- hnix-store-remote/{tests => tests-io}/Driver.hs | 0 hnix-store-remote/{tests => tests-io}/NixDaemon.hs | 0 hnix-store-remote/{tests => tests-io}/Spec.hs | 0 hnix-store-remote/tests/Util.hs | 12 ------------ 5 files changed, 4 insertions(+), 17 deletions(-) rename hnix-store-remote/{tests => tests-io}/Driver.hs (100%) rename hnix-store-remote/{tests => tests-io}/NixDaemon.hs (100%) rename hnix-store-remote/{tests => tests-io}/Spec.hs (100%) delete mode 100644 hnix-store-remote/tests/Util.hs diff --git a/hnix-store-remote/hnix-store-remote.cabal b/hnix-store-remote/hnix-store-remote.cabal index 2153268..fb30eef 100644 --- a/hnix-store-remote/hnix-store-remote.cabal +++ b/hnix-store-remote/hnix-store-remote.cabal @@ -97,7 +97,7 @@ executable remote-readme main-is: README.lhs ghc-options: -pgmL markdown-unlit -Wall -test-suite hnix-store-remote-tests +test-suite remote-io import: commons if !flag(io-testsuite) || os(darwin) @@ -110,10 +110,7 @@ test-suite hnix-store-remote-tests other-modules: NixDaemon , Spec - , Util - hs-source-dirs: tests - build-tool-depends: - tasty-discover:tasty-discover + hs-source-dirs: tests-io build-depends: base , bytestring @@ -135,6 +132,8 @@ test-suite hnix-store-remote-tests , temporary , unix , unordered-containers + build-tool-depends: + tasty-discover:tasty-discover mixins: base hiding (Prelude) , relude (Relude as Prelude) diff --git a/hnix-store-remote/tests/Driver.hs b/hnix-store-remote/tests-io/Driver.hs similarity index 100% rename from hnix-store-remote/tests/Driver.hs rename to hnix-store-remote/tests-io/Driver.hs diff --git a/hnix-store-remote/tests/NixDaemon.hs b/hnix-store-remote/tests-io/NixDaemon.hs similarity index 100% rename from hnix-store-remote/tests/NixDaemon.hs rename to hnix-store-remote/tests-io/NixDaemon.hs diff --git a/hnix-store-remote/tests/Spec.hs b/hnix-store-remote/tests-io/Spec.hs similarity index 100% rename from hnix-store-remote/tests/Spec.hs rename to hnix-store-remote/tests-io/Spec.hs diff --git a/hnix-store-remote/tests/Util.hs b/hnix-store-remote/tests/Util.hs deleted file mode 100644 index dcb61fb..0000000 --- a/hnix-store-remote/tests/Util.hs +++ /dev/null @@ -1,12 +0,0 @@ - -module Util where - -import Data.Text.Arbitrary () -import System.Nix.Store.Remote.Util -import Test.Tasty.QuickCheck - -prop_TextToBSLRoundtrip :: Text -> Property -prop_TextToBSLRoundtrip x = bslToText (textToBSL x) === x - -prop_TextToBSRoundtrip :: Text -> Property -prop_TextToBSRoundtrip x = bsToText (textToBS x) === x From 2a6fd965f6657c679ae171113d765e7a8bd42d12 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Tue, 14 Nov 2023 16:39:22 +0100 Subject: [PATCH 08/13] remote: common - add RecordWildCards, ScopedTypeVariables --- hnix-store-remote/hnix-store-remote.cabal | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/hnix-store-remote/hnix-store-remote.cabal b/hnix-store-remote/hnix-store-remote.cabal index fb30eef..94a5aa3 100644 --- a/hnix-store-remote/hnix-store-remote.cabal +++ b/hnix-store-remote/hnix-store-remote.cabal @@ -13,7 +13,7 @@ category: Nix build-type: Simple extra-source-files: ChangeLog.md, README.md -Common commons +common commons if impl(ghc >= 8.10) ghc-options: -Wall -Wunused-packages else @@ -28,6 +28,8 @@ Common commons , DeriveLift , FlexibleContexts , FlexibleInstances + , RecordWildCards + , ScopedTypeVariables , StandaloneDeriving , TypeApplications , TypeSynonymInstances From 5dc1802665122df97f1c94c71e1cded3a83b47b6 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Wed, 15 Nov 2023 07:12:03 +0100 Subject: [PATCH 09/13] core: move Arbitrary instances near their types This allows us to use them in remote serialization round trip props. Couple of them are not needed anymore (`NixLike` is the default now) so whole `tests/Arbitrary` is gone. --- hnix-store-core/hnix-store-core.cabal | 2 +- .../src/System/Nix/Internal/StorePath.hs | 21 +++++++ hnix-store-core/tests/Arbitrary.hs | 58 ------------------- hnix-store-core/tests/Hash.hs | 7 ++- hnix-store-core/tests/StorePath.hs | 21 ++----- 5 files changed, 34 insertions(+), 75 deletions(-) delete mode 100644 hnix-store-core/tests/Arbitrary.hs diff --git a/hnix-store-core/hnix-store-core.cabal b/hnix-store-core/hnix-store-core.cabal index 7dd5bd6..f21a66d 100644 --- a/hnix-store-core/hnix-store-core.cabal +++ b/hnix-store-core/hnix-store-core.cabal @@ -70,6 +70,7 @@ library , monad-control , mtl , nix-derivation >= 1.1.1 && <2 + , QuickCheck , saltine , time , text @@ -114,7 +115,6 @@ test-suite format-tests type: exitcode-stdio-1.0 main-is: Driver.hs other-modules: - Arbitrary Derivation NarFormat Hash diff --git a/hnix-store-core/src/System/Nix/Internal/StorePath.hs b/hnix-store-core/src/System/Nix/Internal/StorePath.hs index 4ded6ad..e062eca 100644 --- a/hnix-store-core/src/System/Nix/Internal/StorePath.hs +++ b/hnix-store-core/src/System/Nix/Internal/StorePath.hs @@ -49,6 +49,8 @@ import Crypto.Hash ( SHA256 , HashAlgorithm ) +import Test.QuickCheck + -- | A path in a Nix store. -- -- From the Nix thesis: A store path is the full path of a store @@ -72,6 +74,12 @@ instance Hashable StorePath where hashWithSalt s StorePath{..} = s `hashWithSalt` storePathHash `hashWithSalt` storePathName +instance Arbitrary StorePath where + arbitrary = + liftA2 StorePath + arbitrary + arbitrary + -- | The name portion of a Nix path. -- -- 'unStorePathName' must only contain a-zA-Z0-9+._?=-, can't start @@ -82,6 +90,13 @@ newtype StorePathName = StorePathName unStorePathName :: Text } deriving (Eq, Hashable, Ord, Show) +instance Arbitrary StorePathName where + arbitrary = StorePathName . toText <$> ((:) <$> s1 <*> listOf sn) + where + alphanum = ['a' .. 'z'] <> ['A' .. 'Z'] <> ['0' .. '9'] + s1 = elements $ alphanum <> "+-_?=" + sn = elements $ alphanum <> "+-._?=" + -- | The hash algorithm used for store path hashes. newtype StorePathHashPart = StorePathHashPart { -- | Extract the contents of the hash. @@ -89,6 +104,9 @@ newtype StorePathHashPart = StorePathHashPart } deriving (Eq, Hashable, Ord, Show) +instance Arbitrary StorePathHashPart where + arbitrary = mkStorePathHashPart @SHA256 . Bytes.Char8.pack <$> arbitrary + mkStorePathHashPart :: forall hashAlgo . HashAlgorithm hashAlgo @@ -167,6 +185,9 @@ newtype StoreDir = StoreDir { unStoreDir :: RawFilePath } deriving (Eq, Hashable, Ord, Show) +instance Arbitrary StoreDir where + arbitrary = StoreDir . ("/" <>) . Bytes.Char8.pack <$> arbitrary + -- | Render a 'StorePath' as a 'RawFilePath'. storePathToRawFilePath :: StoreDir -> StorePath -> RawFilePath storePathToRawFilePath storeDir StorePath{..} = diff --git a/hnix-store-core/tests/Arbitrary.hs b/hnix-store-core/tests/Arbitrary.hs deleted file mode 100644 index dcf40aa..0000000 --- a/hnix-store-core/tests/Arbitrary.hs +++ /dev/null @@ -1,58 +0,0 @@ -{-# language DataKinds #-} -{-# OPTIONS_GHC -Wno-orphans #-} - -module Arbitrary where - -import qualified Data.ByteString.Char8 as BSC - -import Test.Tasty.QuickCheck - -import System.Nix.Internal.StorePath -import Crypto.Hash ( SHA256 - , Digest - , hash - ) - -genSafeChar :: Gen Char -genSafeChar = choose ('\1', '\127') -- ASCII without \NUL - -nonEmptyString :: Gen String -nonEmptyString = listOf1 genSafeChar - -dir :: Gen String -dir = ('/':) <$> listOf1 (elements $ '/':['a'..'z']) - -instance Arbitrary StorePathName where - arbitrary = StorePathName . toText <$> ((:) <$> s1 <*> listOf sn) - where - alphanum = ['a' .. 'z'] <> ['A' .. 'Z'] <> ['0' .. '9'] - s1 = elements $ alphanum <> "+-_?=" - sn = elements $ alphanum <> "+-._?=" - -instance Arbitrary StorePathHashPart where - arbitrary = mkStorePathHashPart @SHA256 . BSC.pack <$> arbitrary - -instance Arbitrary (Digest SHA256) where - arbitrary = hash . BSC.pack <$> arbitrary - -instance Arbitrary StoreDir where - arbitrary = StoreDir . ("/" <>) . BSC.pack <$> arbitrary - -newtype NixLike = NixLike {getNixLike :: StorePath} - deriving (Eq, Ord, Show) - -instance Arbitrary NixLike where - arbitrary = - NixLike <$> - liftA2 StorePath - arbitraryTruncatedDigest - arbitrary - where - -- 160-bit hash, 20 bytes, 32 chars in base32 - arbitraryTruncatedDigest = coerce . BSC.pack <$> replicateM 20 genSafeChar - -instance Arbitrary StorePath where - arbitrary = - liftA2 StorePath - arbitrary - arbitrary diff --git a/hnix-store-core/tests/Hash.hs b/hnix-store-core/tests/Hash.hs index 9a78342..866fa06 100644 --- a/hnix-store-core/tests/Hash.hs +++ b/hnix-store-core/tests/Hash.hs @@ -13,7 +13,6 @@ import Test.Tasty.QuickCheck import System.Nix.Hash import System.Nix.StorePath -import Arbitrary import System.Nix.Internal.Base import Crypto.Hash ( MD5 , SHA1 @@ -49,6 +48,12 @@ spec_hash = do prop_nixBase32Roundtrip :: Property prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $ \x -> pure (encodeUtf8 x) === (B32.decode . B32.encode . encodeUtf8 $ x) + where + nonEmptyString :: Gen String + nonEmptyString = listOf1 genSafeChar + + genSafeChar :: Gen Char + genSafeChar = choose ('\1', '\127') -- ASCII without \NUL -- | API variants prop_nixBase16Roundtrip :: StorePathHashPart -> Property diff --git a/hnix-store-core/tests/StorePath.hs b/hnix-store-core/tests/StorePath.hs index 2fd9d4e..e1977a2 100644 --- a/hnix-store-core/tests/StorePath.hs +++ b/hnix-store-core/tests/StorePath.hs @@ -9,22 +9,13 @@ import qualified Data.Attoparsec.Text import Test.Tasty.QuickCheck import System.Nix.StorePath -import Arbitrary --- | Test that Nix(OS) like paths roundtrip -prop_storePathRoundtrip :: StoreDir -> NixLike -> NixLike -> Property -prop_storePathRoundtrip storeDir (_ :: NixLike) (NixLike x) = +-- | Test @StorePath@ roundtrips using @parsePath@ +prop_storePathRoundtrip :: StoreDir -> StorePath -> Property +prop_storePathRoundtrip storeDir x = parsePath storeDir (storePathToRawFilePath storeDir x) === pure x --- | Test that any `StorePath` roundtrips -prop_storePathRoundtrip' :: StoreDir -> StorePath -> Property -prop_storePathRoundtrip' storeDir x = - parsePath storeDir (storePathToRawFilePath storeDir x) === pure x - -prop_storePathRoundtripParser :: StoreDir -> NixLike -> NixLike -> Property -prop_storePathRoundtripParser storeDir (_ :: NixLike) (NixLike x) = - Data.Attoparsec.Text.parseOnly (pathParser storeDir) (storePathToText storeDir x) === pure x - -prop_storePathRoundtripParser' :: StoreDir -> StorePath -> Property -prop_storePathRoundtripParser' storeDir x = +-- | Test @StorePath@ roundtrips using @pathParser@ +prop_storePathRoundtripParser :: StoreDir -> StorePath -> Property +prop_storePathRoundtripParser storeDir x = Data.Attoparsec.Text.parseOnly (pathParser storeDir) (storePathToText storeDir x) === pure x From 522244b216aca7d61a0fd54a460f8185b4ba150a Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Wed, 15 Nov 2023 08:40:29 +0100 Subject: [PATCH 10/13] core: CHANGELOG --- hnix-store-core/ChangeLog.md | 37 ++++++++++++++++++++++++------------ 1 file changed, 25 insertions(+), 12 deletions(-) diff --git a/hnix-store-core/ChangeLog.md b/hnix-store-core/ChangeLog.md index 50ed778..6ed058c 100644 --- a/hnix-store-core/ChangeLog.md +++ b/hnix-store-core/ChangeLog.md @@ -1,6 +1,19 @@ -# ChangeLog +# Next -## [0.7.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.1.0...core-0.7.0.0) 2023-11-15 +* Changes: + * Constructors of `StorePathName` and `StorePathHashPart` are no longer + exported. Use respective `mkStorePath..` functions. [#230](https://github.com/haskell-nix/hnix-store/pull/230) + * `StorePathSet` type alias is no more, use `HashSet StorePath` [#230](https://github.com/haskell-nix/hnix-store/pull/230) + + +* Additions: + * Added `Arbitrary` instances for (exported by default) [#230](https://github.com/haskell-nix/hnix-store/pull/230) + * `StorePath` + * `StorePathName` + * `StorePathHashPart` + * `StoreDir` + +# [0.7.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.1.0...core-0.7.0.0) 2023-11-15 * Breaking: * [(link)](https://github.com/haskell-nix/hnix-store/pull/216) `StorePath` no longer carries `storePathRoot` field and we @@ -14,13 +27,13 @@ * `data NarOptions` has been added to configure NAR encoding and decoding. The `optUseCaseHack` field can be used to enable or disable the case hack. * New `streamNarIOWithOptions` and `runParserWithOptions` functions have been added to `System.Nix.Nar` to support the new configurable options. -## [0.6.1.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.0.0...core-0.6.1.0) 2023-01-02 +# [0.6.1.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.0.0...core-0.6.1.0) 2023-01-02 * Fixed: * [(link)](https://github.com/haskell-nix/hnix-store/pull/201) [(link)](https://github.com/haskell-nix/hnix-store/pull/203) NAR serialization compatibility (symlinks, directory symlinks, UTF-8 handling) -## [0.6.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.5.0.0...core-0.6.0.0) 2022-06-06 +# [0.6.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.5.0.0...core-0.6.0.0) 2022-06-06 * Breaking: @@ -28,7 +41,7 @@ * `FilePath` can turn to `NarSource m` using `dumpPath` * `ByteString` can turn to `NarSource m` using `dumpString` -## [0.5.0.0](https://github.com/haskell-nix/hnix-store/compare/0.4.3.0...core-0.5.0.0) 2021-06-10 +# [0.5.0.0](https://github.com/haskell-nix/hnix-store/compare/0.4.3.0...core-0.5.0.0) 2021-06-10 * Breaking: @@ -63,14 +76,14 @@ `mkStorePathHash :: HashAlgorithm a => ByteString -> ByteString` but recommend to at once use `mkStorePathHashPart`. -## [0.4.3.0](https://github.com/haskell-nix/hnix-store/compare/0.4.2.0...0.4.3.0) 2021-05-30 +# [0.4.3.0](https://github.com/haskell-nix/hnix-store/compare/0.4.2.0...0.4.3.0) 2021-05-30 * Additional: * [(link)](https://github.com/haskell-nix/hnix-store/commit/b85f7c875fe6b0bca939ffbcd8b9bd0ab1598aa0) `System.Nix.ReadonlyStore`: add a readonly `computeStorePathForPath` * [(link)](https://github.com/haskell-nix/hnix-store/commit/db71ecea3109c0ba270fa98a9041a8556e35217f) `System.Nix.ReadonlyStore`: `computeStorePathForPath`: force SHA256 as it's the only valid choice * [(link)](https://github.com/haskell-nix/hnix-store/commit/5fddf3c66ba1bcabb72c4d6b6e09fb41a7acd62c): `makeTextPath`: order the references -## [0.4.2.0](https://github.com/haskell-nix/hnix-store/compare/0.4.1.0...0.4.2.0) 2021-03-12 +# [0.4.2.0](https://github.com/haskell-nix/hnix-store/compare/0.4.1.0...0.4.2.0) 2021-03-12 * Additional: @@ -85,18 +98,18 @@ * [(link)](https://github.com/haskell-nix/hnix-store/commit/2a897ab581c0501587ce04da6d6e3a6f543b1d72) Test suite: fixed nar test for the envs without `/proc` (test suite now works on `macOS`). -## [0.4.1.0](https://github.com/haskell-nix/hnix-store/compare/0.4.0.0...0.4.1.0) 2021-01-16 +# [0.4.1.0](https://github.com/haskell-nix/hnix-store/compare/0.4.0.0...0.4.1.0) 2021-01-16 * Big clean-up of dependencies. -## [0.4.0.0](https://github.com/haskell-nix/hnix-store/compare/0.3.0.0...0.4.0.0) 2020-12-30 +# [0.4.0.0](https://github.com/haskell-nix/hnix-store/compare/0.3.0.0...0.4.0.0) 2020-12-30 * `System.Nix.Hash` no longer exports `encodeBase16, decodeBase16` and their `Base32` counterparts. These were replaced by `encodeInBase` and `decodeBase` functions accepting `BaseEncoding` data type [#87](https://github.com/haskell-nix/hnix-store/pull/87) * Support `base16-bytestring >= 1` [#86](https://github.com/haskell-nix/hnix-store/pull/86) [#100](https://github.com/haskell-nix/hnix-store/pull/100) -## 0.3.0.0 -- 2020-11-29 +# 0.3.0.0 -- 2020-11-29 * `System.Nix.Nar` changes API to support NAR format streaming: * `buildNarIO :: FilePath -> Handle -> IO ()` - Create a NAR from a regular filesystem object, stream it out on the Handle @@ -115,11 +128,11 @@ symbolic store path root. * Removed `System.Nix.Util` module, moved to `hnix-store-remote` * Added base64 and SHA512 hash support -## 0.2.0.0 -- 2020-03-12 +# 0.2.0.0 -- 2020-03-12 Removed `System.Nix.Store`. We may reintroduce it later when multiple backends exist and we can tell what common effects they should share. -## 0.1.0.0 -- 2019-03-18 +# 0.1.0.0 -- 2019-03-18 * First version. From 82fc838af08959453df85f090fc58c7e5471e6eb Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Wed, 15 Nov 2023 08:42:56 +0100 Subject: [PATCH 11/13] ChangeLog.md -> CHANGELOG.md, add README.lhs for remote --- hnix-store-core/{ChangeLog.md => CHANGELOG.md} | 0 hnix-store-core/hnix-store-core.cabal | 2 +- hnix-store-remote/{ChangeLog.md => CHANGELOG.md} | 0 hnix-store-remote/hnix-store-remote.cabal | 5 ++++- 4 files changed, 5 insertions(+), 2 deletions(-) rename hnix-store-core/{ChangeLog.md => CHANGELOG.md} (100%) rename hnix-store-remote/{ChangeLog.md => CHANGELOG.md} (100%) diff --git a/hnix-store-core/ChangeLog.md b/hnix-store-core/CHANGELOG.md similarity index 100% rename from hnix-store-core/ChangeLog.md rename to hnix-store-core/CHANGELOG.md diff --git a/hnix-store-core/hnix-store-core.cabal b/hnix-store-core/hnix-store-core.cabal index f21a66d..8f14344 100644 --- a/hnix-store-core/hnix-store-core.cabal +++ b/hnix-store-core/hnix-store-core.cabal @@ -15,7 +15,7 @@ copyright: 2018 Shea Levy category: Nix build-type: Simple extra-source-files: - ChangeLog.md + CHANGELOG.md , README.md , tests/samples/example0.drv , tests/samples/example1.drv diff --git a/hnix-store-remote/ChangeLog.md b/hnix-store-remote/CHANGELOG.md similarity index 100% rename from hnix-store-remote/ChangeLog.md rename to hnix-store-remote/CHANGELOG.md diff --git a/hnix-store-remote/hnix-store-remote.cabal b/hnix-store-remote/hnix-store-remote.cabal index 94a5aa3..d443d2c 100644 --- a/hnix-store-remote/hnix-store-remote.cabal +++ b/hnix-store-remote/hnix-store-remote.cabal @@ -11,7 +11,10 @@ maintainer: srk@48.io copyright: 2018 Richard Marko category: Nix build-type: Simple -extra-source-files: ChangeLog.md, README.md +extra-source-files: + CHANGELOG.md + , README.md + , README.lhs common commons if impl(ghc >= 8.10) From e81932aa77cd030bde183b3d905450a37a0e8251 Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Wed, 15 Nov 2023 08:49:38 +0100 Subject: [PATCH 12/13] remote: CHANGELOG cleanup --- hnix-store-remote/CHANGELOG.md | 48 +++++++++++++++------------------- 1 file changed, 21 insertions(+), 27 deletions(-) diff --git a/hnix-store-remote/CHANGELOG.md b/hnix-store-remote/CHANGELOG.md index 19e3a4f..c7b0bec 100644 --- a/hnix-store-remote/CHANGELOG.md +++ b/hnix-store-remote/CHANGELOG.md @@ -1,60 +1,54 @@ -# Revision history for hnix-store-remote +# Unreleased 202y-mm-dd -## Unreleased 202y-mm-dd - -* Breaking: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/216) `StorePath` no longer carries `storePathRoot` field and we +* Changes: + * `StorePath` no longer carries `storePathRoot` field and we have a stand-alone `StoreDir` type instead to be used instead of `FilePath` when store root directory is needed as a context. - Fore `-remote`, this affects `runStoreOpts` and its variants. + Fore `-remote`, this affects `runStoreOpts` and its variants [#216](https://github.com/haskell-nix/hnix-store/pull/216) -## [0.6.0.0](https://github.com/haskell-nix/hnix-store/compare/remote-0.5.0.0...remote-0.6.0.0) 2021-06-06 +# [0.6.0.0](https://github.com/haskell-nix/hnix-store/compare/remote-0.5.0.0...remote-0.6.0.0) 2021-06-06 -* Breaking: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/179) `System.Nix.Store.Remote`: +* Changes: + * `System.Nix.Store.Remote` [#179](https://github.com/haskell-nix/hnix-store/pull/179) * `addToStore` no longer accepts `FilePath` as its second argument but uses more generic `NarSource` [(NarSource PR)](https://github.com/haskell-nix/hnix-store/pull/177) -## [0.5.0.0](https://github.com/haskell-nix/hnix-store/compare/0.4.3.0...remote-0.5.0.0) 2021-06-11 +# [0.5.0.0](https://github.com/haskell-nix/hnix-store/compare/0.4.3.0...remote-0.5.0.0) 2021-06-11 -* Breaking: - * [(link)](https://github.com/haskell-nix/hnix-store/commit/3b948d112aa9307b0451258f28c7ee5dc86b24c7) `System.Nix.Store.Remote`: +* Changes: + * `System.Nix.Store.Remote` [#161](https://github.com/haskell-nix/hnix-store/pull/161) * `addToStore`: constraint of `ValidAlgo a` removed in favour of constraint on `cryptonite: HashAlgorithm a` through constraint `NamedAlgo a`. * `queryPathFromHashPart`: 1st arg changed from `Digest StorePathHashAlgo` to `StorePathHashPart`, for details: [hnix-store-core 0.5.0.0 ChangeLog](https://hackage.haskell.org/package/hnix-store-core-0.5.0.0/changelog). -## [0.4.3.0](https://github.com/haskell-nix/hnix-store/compare/0.4.2.0...0.4.3.0) 2021-05-30 +# [0.4.3.0](https://github.com/haskell-nix/hnix-store/compare/0.4.2.0...0.4.3.0) 2021-05-30 Nothing (it is tandem `hnix-store-core` fix release) -## [0.4.2.0](https://github.com/haskell-nix/hnix-store/compare/0.4.1.0...0.4.2.0) 2021-03-12 +# [0.4.2.0](https://github.com/haskell-nix/hnix-store/compare/0.4.1.0...0.4.2.0) 2021-03-12 -* Additional: +* Additions: + * Cabal now properly states `tasty-discover` as `build-tool-depends` [#130](https://github.com/haskell-nix/hnix-store/pull/130) + * added explicit `hie.yml` cradle description for `cabal` to help Haskell Language Server to work with monorepo. [#132](https://github.com/haskell-nix/hnix-store/pull/132) + * Nix dev env: removed GHC 8.6.5 support, afaik it is not even in Nixpkgs anymore [#136](https://github.com/haskell-nix/hnix-store/pull/136) - * [(link)](https://github.com/haskell-nix/hnix-store/commit/5d03ffc43cde9448df05e84838ece70cc83b1b6c) Cabal now properly states `tasty-discover` as `build-tool-depends`. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/b5ad38573d27e0732d0fadfebd98de1f753b4f07) added explicit `hie.yml` cradle description for `cabal` to help Haskell Language Server to work with monorepo. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/cf04083aba98ad40d183d1e26251101816cc07ae) Nix dev env: removed GHC 8.6.5 support, afaik it is not even in Nixpkgs anymore. - - -## [0.4.1.0](https://github.com/haskell-nix/hnix-store/compare/0.4.0.0...0.4.1.0) 2021-01-16 +# [0.4.1.0](https://github.com/haskell-nix/hnix-store/compare/0.4.0.0...0.4.1.0) 2021-01-16 * `System.Nix.Store.Remote`: module API now re-exports `System.Nix.Store.Remote.Types` API * Big clean-up of dependencies. -## [0.4.0.0](https://github.com/haskell-nix/hnix-store/compare/0.3.0.0...0.4.0.0) 2020-12-30 +# [0.4.0.0](https://github.com/haskell-nix/hnix-store/compare/0.3.0.0...0.4.0.0) 2020-12-30 * `hnix-store-core` compatibility -## 0.3.0.0 -- 2020-11-29 +# 0.3.0.0 -- 2020-11-29 * Restored most store API functions except `addToStoreNar` * Added `buildDerivation` -## 0.2.0.0 -- skipped +# 0.2.0.0 -- skipped * `hnix-store-core` release only -## 0.1.0.0 -- 2019-03-18 +# 0.1.0.0 -- 2019-03-18 * First version. From 863852d353a64679b46cc331d9f3c7bbfae5a30c Mon Sep 17 00:00:00 2001 From: Richard Marko Date: Wed, 15 Nov 2023 09:01:10 +0100 Subject: [PATCH 13/13] core: CHANGELOG cleanup --- hnix-store-core/CHANGELOG.md | 58 ++++++++++++++++-------------------- 1 file changed, 26 insertions(+), 32 deletions(-) diff --git a/hnix-store-core/CHANGELOG.md b/hnix-store-core/CHANGELOG.md index 6ed058c..b006cfa 100644 --- a/hnix-store-core/CHANGELOG.md +++ b/hnix-store-core/CHANGELOG.md @@ -5,7 +5,6 @@ exported. Use respective `mkStorePath..` functions. [#230](https://github.com/haskell-nix/hnix-store/pull/230) * `StorePathSet` type alias is no more, use `HashSet StorePath` [#230](https://github.com/haskell-nix/hnix-store/pull/230) - * Additions: * Added `Arbitrary` instances for (exported by default) [#230](https://github.com/haskell-nix/hnix-store/pull/230) * `StorePath` @@ -15,29 +14,31 @@ # [0.7.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.1.0...core-0.7.0.0) 2023-11-15 -* Breaking: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/216) `StorePath` no longer carries `storePathRoot` field and we +* Changes: + * `StorePath` no longer carries `storePathRoot` field and we have a stand-alone `StoreDir` type instead to be used instead of `FilePath` - when store root directory is needed as a context. + when store root directory is needed as a context [#216](https://github.com/haskell-nix/hnix-store/pull/216) -* Additional: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/218) NAR encoding and decoding now supports case-insensitive filesystems. +* Fixes: + * NAR encoding and decoding now supports case-insensitive filesystems [#218](https://github.com/haskell-nix/hnix-store/pull/218) * The "case hack" replicates the behavior of the `use-case-hack` option in Nix, which adds a suffix to conflicting filenames. This feature is enabled by default on macOS (darwin). - * `data NarOptions` has been added to configure NAR encoding and decoding. The `optUseCaseHack` field can be used to enable or disable the case hack. - * New `streamNarIOWithOptions` and `runParserWithOptions` functions have been added to `System.Nix.Nar` to support the new configurable options. + +* Additions: + * `data NarOptions` has been added to configure NAR encoding and decoding. The `optUseCaseHack` field can be used to enable or disable the case hack [#218](https://github.com/haskell-nix/hnix-store/pull/218) + * New `streamNarIOWithOptions` and `runParserWithOptions` functions have been added to `System.Nix.Nar` to support the new configurable options [#218](https://github.com/haskell-nix/hnix-store/pull/218) # [0.6.1.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.0.0...core-0.6.1.0) 2023-01-02 -* Fixed: +* Fixes: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/201) [(link)](https://github.com/haskell-nix/hnix-store/pull/203) NAR serialization compatibility (symlinks, directory symlinks, UTF-8 handling) + * NAR serialization compatibility (symlinks, directory symlinks, UTF-8 handling) [#201](https://github.com/haskell-nix/hnix-store/pull/201) [#203](https://github.com/haskell-nix/hnix-store/pull/203) # [0.6.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.5.0.0...core-0.6.0.0) 2022-06-06 * Breaking: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/177) `streamNarIO` changes type and returns `NarSource m` + * `streamNarIO` changes type and returns `NarSource m` [#177](https://github.com/haskell-nix/hnix-store/pull/177) * `FilePath` can turn to `NarSource m` using `dumpPath` * `ByteString` can turn to `NarSource m` using `dumpString` @@ -46,31 +47,29 @@ * Breaking: * `System.Nix.Hash`: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/97146b41cc87327625e02b81971aeb2fd7d66a3f) Migration from packages `cryptohash-` -> `cryptonite`: + * Migration from packages `cryptohash-` -> `cryptonite` [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/97146b41cc87327625e02b81971aeb2fd7d66a3f) * rm `newtype Digest` in favour of `cryptonite: newtype Digest` * rm `data HashAlgorithm` in favour of `cryptonite: class HashAlgorithm` * rm `class ValidAlgo` in favour of `cryptonite: class HashAlgorithm`. * `class NamedAlgo` removed `hashSize` in favour of `cryptonite: class HashAlgorithm: hashDigestSize`. Former became a subclass of the latter. * rm `hash` in favour of `cryptonite: hash` * rm `hashLazy` in favour of `cryptonite: hashlazy` - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) Base encoding/decoding function for hashes (digests) changed (due to changes in type system & separation of specially truncated Nix Store hasing): + * Base encoding/decoding function for hashes (digests) changed (due to changes in type system & separation of specially truncated Nix Store hasing) [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) * `encode(InBase -> DigestWith)` * `decode(Base -> DigestWith)` - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) `System.Nix.StorePath`: + * `System.Nix.StorePath` [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) * rm `type StorePathHashAlgo = 'Truncated 20 'SHA256` in favour of `StorePathHashPart` & `mkStorePathHashPart`. * rm `unStorePathName`, please use `GHC: coerce` for `StorePathName <-> Text`, `StorePathName` data constructor is provided. * `Internal` modules now have export lists, if something, please contact. - * Additional: - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/97146b41cc87327625e02b81971aeb2fd7d66a3f) Support of GHC 9.0. - - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) `System.Nix.StorePath`: + * Support of GHC 9.0 [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/97146b41cc87327625e02b81971aeb2fd7d66a3f) + * `System.Nix.StorePath` [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) * exposed `StorePathName` data constructor to API. * added `newtype StorePathHashPart = StorePathHashPart ByteString`. * added builder `mkStorePathHashPart :: ByteString -> StorePathHashPart` - * [(link)](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) `System.Nix.Hash`: + * `System.Nix.Hash` [#157](https://github.com/haskell-nix/hnix-store/pull/157/commits/2af74986de8aef1a13dbfc955886f9935ca246a3) * Nix store (which are specially truncated) hashes are now handled separately from other hashes: * add `mkStorePathHash` - a function to create a content into Nix storepath-style hash: `mkStorePathHash :: HashAlgorithm a => ByteString -> ByteString` @@ -79,23 +78,18 @@ # [0.4.3.0](https://github.com/haskell-nix/hnix-store/compare/0.4.2.0...0.4.3.0) 2021-05-30 * Additional: - * [(link)](https://github.com/haskell-nix/hnix-store/commit/b85f7c875fe6b0bca939ffbcd8b9bd0ab1598aa0) `System.Nix.ReadonlyStore`: add a readonly `computeStorePathForPath` - * [(link)](https://github.com/haskell-nix/hnix-store/commit/db71ecea3109c0ba270fa98a9041a8556e35217f) `System.Nix.ReadonlyStore`: `computeStorePathForPath`: force SHA256 as it's the only valid choice - * [(link)](https://github.com/haskell-nix/hnix-store/commit/5fddf3c66ba1bcabb72c4d6b6e09fb41a7acd62c): `makeTextPath`: order the references + * `System.Nix.ReadonlyStore`: add a readonly `computeStorePathForPath` [b85f7c8](https://github.com/haskell-nix/hnix-store/commit/b85f7c875fe6b0bca939ffbcd8b9bd0ab1598aa0) + * `System.Nix.ReadonlyStore`: `computeStorePathForPath`: force SHA256 as it's the only valid choice [db71ece](https://github.com/haskell-nix/hnix-store/commit/db71ecea3109c0ba270fa98a9041a8556e35217f) + * `makeTextPath`: order the references [5fddf3c](https://github.com/haskell-nix/hnix-store/commit/5fddf3c66ba1bcabb72c4d6b6e09fb41a7acd62c) # [0.4.2.0](https://github.com/haskell-nix/hnix-store/compare/0.4.1.0...0.4.2.0) 2021-03-12 * Additional: - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/5d03ffc43cde9448df05e84838ece70cc83b1b6c) Cabal now properly states `tasty-discover` as `build-tool-depends`. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/b5ad38573d27e0732d0fadfebd98de1f753b4f07) added explicit `hie.yml` cradle description for `cabal` to help Haskell Language Server to work with monorepo. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/a5b7a614c0e0e11147a93b9a197c2a443afa3244) rm vacuous `Setup.hs`, it was throwing-off HLS, and anyway file is vacuous and gets deprecated by Cabal itself. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/cf04083aba98ad40d183d1e26251101816cc07ae) Nix dev env: removed GHC 8.6.5 support, afaik it is not even in Nixpkgs anymore. - - * [(link)](https://github.com/haskell-nix/hnix-store/commit/2a897ab581c0501587ce04da6d6e3a6f543b1d72) Test suite: fixed nar test for the envs without `/proc` (test suite now works on `macOS`). + * Cabal now properly states `tasty-discover` as `build-tool-depends` [5d03ffc](https://github.com/haskell-nix/hnix-store/commit/5d03ffc4cde9448df05e84838ece70cc83b1b6c) + * Added explicit `hie.yml` cradle description for `cabal` to help Haskell Language Server to work with monorepo [5bad385](https://github.com/haskell-nix/hnix-store/commit/b5ad38573d27e0732d0fadfebd98de1f753b4f07) + * Removed vacuous `Setup.hs`, it was throwing-off HLS, and anyway file is vacuous and gets deprecated by Cabal itself [a5b7a61](https://github.com/haskell-nix/hnix-store/commit/a5b7a614c0e0e11147a93b9a197c2a443afa3244) + * Nix dev env: removed GHC 8.6.5 support, afaik it is not even in Nixpkgs anymore [cf04083](https://github.com/haskell-nix/hnix-store/commit/cf04083aba98ad40d183d1e26251101816cc07ae) + * Test suite: fixed nar test for the envs without `/proc` (test suite now works on `macOS`) [2a897ab](https://github.com/haskell-nix/hnix-store/commit/2a897ab581c0501587ce04da6d6e3a6f543b1d72) # [0.4.1.0](https://github.com/haskell-nix/hnix-store/compare/0.4.0.0...0.4.1.0) 2021-01-16