Clean up content address method types

This corresponds to

b51e161af5

and part of

ed26b186fb
This commit is contained in:
John Ericson 2024-10-31 10:54:12 -04:00
parent 12b48aeb4a
commit 43fc6d4bf2
15 changed files with 109 additions and 90 deletions

View File

@ -64,6 +64,7 @@ library
, System.Nix.Derivation
, System.Nix.DerivedPath
, System.Nix.Fingerprint
, System.Nix.FileContentAddress
, System.Nix.Hash
, System.Nix.Hash.Truncation
, System.Nix.OutputName

View File

@ -1,9 +1,8 @@
{-# LANGUAGE OverloadedStrings #-}
module System.Nix.ContentAddress (
ContentAddress
, ContentAddressMethod
, FileIngestionMethod
ContentAddress (..)
, ContentAddressMethod (..)
, contentAddressBuilder
, contentAddressParser
, buildContentAddress
@ -18,7 +17,6 @@ import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import GHC.Generics (Generic)
import System.Nix.Hash (HashAlgo)
import System.Nix.Store.Types (FileIngestionMethod(..))
import qualified Data.Attoparsec.Text
import qualified Data.Text.Lazy
@ -26,11 +24,9 @@ import qualified Data.Text.Lazy.Builder
import qualified System.Nix.Hash
data ContentAddressMethod
= FileIngestionMethod !FileIngestionMethod
-- ^ The path was added to the store via makeFixedOutputPath or
-- addToStore. It is addressed according to some hash algorithm
-- applied to the nar serialization via some 'NarHashMode'.
| TextIngestionMethod
= ContentAddressMethod_Flat
| ContentAddressMethod_NixArchive
| ContentAddressMethod_Text
-- ^ The path is a plain file added via makeTextPath or
-- addTextToStore. It is addressed according to a sha256sum of the
-- file contents.
@ -59,19 +55,14 @@ buildContentAddress =
. contentAddressBuilder
contentAddressBuilder :: ContentAddress -> Builder
contentAddressBuilder (ContentAddress method digest) = case method of
TextIngestionMethod ->
"text:"
<> System.Nix.Hash.algoDigestBuilder digest
FileIngestionMethod r ->
"fixed:"
<> fileIngestionMethodBuilder r
<> System.Nix.Hash.algoDigestBuilder digest
fileIngestionMethodBuilder :: FileIngestionMethod -> Builder
fileIngestionMethodBuilder = \case
FileIngestionMethod_Flat -> ""
FileIngestionMethod_NixArchive -> "r:"
contentAddressBuilder (ContentAddress method digest) =
(case method of
ContentAddressMethod_Text -> "text"
ContentAddressMethod_NixArchive -> "fixed:r"
ContentAddressMethod_Flat -> "fixed"
)
<> ":"
<> System.Nix.Hash.algoDigestBuilder digest
-- | Parse `ContentAddressableAddress` from `ByteString`
parseContentAddress
@ -83,6 +74,7 @@ parseContentAddress =
contentAddressParser :: Parser ContentAddress
contentAddressParser = do
method <- parseContentAddressMethod
_ <- ":"
digest <- parseTypedDigest
case digest of
Left e -> fail e
@ -90,10 +82,9 @@ contentAddressParser = do
parseContentAddressMethod :: Parser ContentAddressMethod
parseContentAddressMethod =
TextIngestionMethod <$ "text:"
<|> FileIngestionMethod <$ "fixed:"
<*> (FileIngestionMethod_NixArchive <$ "r:"
<|> pure FileIngestionMethod_Flat)
(ContentAddressMethod_Text <$ "text")
<|> (ContentAddressMethod_NixArchive <$ "fixed:r")
<|> (ContentAddressMethod_Flat <$ "fixed")
parseTypedDigest :: Parser (Either String (DSum HashAlgo Digest))
parseTypedDigest = System.Nix.Hash.mkNamedDigest <$> parseHashType <*> parseHash

View File

@ -0,0 +1,10 @@
module System.Nix.FileContentAddress
( FileIngestionMethod(..)
) where
import GHC.Generics (Generic)
data FileIngestionMethod
= FileIngestionMethod_Flat
| FileIngestionMethod_NixArchive
deriving (Bounded, Eq, Generic, Enum, Ord, Show)

View File

@ -1,17 +1,11 @@
-- | TODO rename module
module System.Nix.Store.Types
( FileIngestionMethod(..)
, PathFilter(..)
( PathFilter(..)
, RepairMode(..)
) where
import GHC.Generics (Generic)
-- | Add path recursively or not
data FileIngestionMethod
= FileIngestionMethod_Flat
| FileIngestionMethod_NixArchive
deriving (Bounded, Eq, Generic, Enum, Ord, Show)
-- | Path filtering function
newtype PathFilter = PathFilter
{ pathFilterFunction :: FilePath -> Bool

View File

@ -2,9 +2,7 @@
module System.Nix.Store.ReadOnly
( makeStorePath
, makeTextPath
, makeFixedOutputPath
, computeStorePathForText
, computeStorePathForPath
) where
@ -12,8 +10,9 @@ import Control.Monad.State (StateT, execStateT, modify)
import Crypto.Hash (Context, Digest, SHA256)
import Data.ByteString (ByteString)
import Data.HashSet (HashSet)
import System.Nix.ContentAddress (ContentAddressMethod (..))
import System.Nix.Hash (BaseEncoding(Base16), NamedAlgo(algoName))
import System.Nix.Store.Types (FileIngestionMethod(..), PathFilter, RepairMode)
import System.Nix.Store.Types (PathFilter, RepairMode)
import System.Nix.StorePath (StoreDir, StorePath, StorePathName)
import qualified Crypto.Hash
@ -49,16 +48,16 @@ makeStorePath storeDir ty h nm =
]
makeTextPath
:: StoreDir
-> StorePathName
-> Digest SHA256
:: NamedAlgo _SHA256
=> StoreDir
-> Digest _SHA256 -- TODO enforce its it again
-> HashSet StorePath
-> StorePathName
-> StorePath
makeTextPath storeDir nm h refs = makeStorePath storeDir ty h nm
makeTextPath storeDir h refs nm = makeStorePath storeDir ty h nm
where
ty =
Data.ByteString.intercalate
":"
Data.ByteString.intercalate ":"
$ "text"
: Data.List.sort
(System.Nix.StorePath.storePathToRawFilePath storeDir
@ -68,50 +67,42 @@ makeFixedOutputPath
:: forall hashAlgo
. NamedAlgo hashAlgo
=> StoreDir
-> FileIngestionMethod
-> ContentAddressMethod
-> Digest hashAlgo
-> HashSet StorePath
-> StorePathName
-> StorePath
makeFixedOutputPath storeDir recursive h =
if recursive == FileIngestionMethod_NixArchive
&& (algoName @hashAlgo) == "sha256"
then makeStorePath storeDir "source" h
else makeStorePath storeDir "output:out" h'
makeFixedOutputPath storeDir method h refs =
case method of
ContentAddressMethod_Text -> makeTextPath storeDir h refs
_ ->
if method == ContentAddressMethod_NixArchive
&& (algoName @hashAlgo) == "sha256"
then makeStorePath storeDir "source" h
else makeStorePath storeDir "output:out" h'
where
h' =
Crypto.Hash.hash @ByteString @SHA256
$ "fixed:out:"
<> Data.Text.Encoding.encodeUtf8 (algoName @hashAlgo)
<> (if recursive == FileIngestionMethod_NixArchive then ":r:" else ":")
<> (if method == ContentAddressMethod_NixArchive then ":r:" else ":")
<> Data.Text.Encoding.encodeUtf8 (System.Nix.Hash.encodeDigestWith Base16 h)
<> ":"
computeStorePathForText
:: StoreDir
-> StorePathName
-> ByteString
-> (HashSet StorePath -> StorePath)
computeStorePathForText storeDir nm =
makeTextPath storeDir nm
. Crypto.Hash.hash
computeStorePathForPath
:: StoreDir
-> StorePathName -- ^ Name part of the newly created `StorePath`
-> FilePath -- ^ Local `FilePath` to add
-> FileIngestionMethod -- ^ Add target directory recursively
digestPath
:: FilePath -- ^ Local `FilePath` to add
-> ContentAddressMethod -- ^ target directory method
-> PathFilter -- ^ Path filter function
-> RepairMode -- ^ Only used by local store backend
-> IO StorePath
computeStorePathForPath storeDir name pth recursive _pathFilter _repair = do
selectedHash <-
if recursive == FileIngestionMethod_NixArchive
then recursiveContentHash
else flatContentHash
pure $ makeFixedOutputPath storeDir recursive selectedHash name
-> IO (Digest SHA256)
digestPath pth method _pathFilter _repair =
case method of
ContentAddressMethod_Flat -> flatContentHash
ContentAddressMethod_NixArchive -> nixArchiveContentHash
ContentAddressMethod_Text -> flatContentHash
where
recursiveContentHash :: IO (Digest SHA256)
recursiveContentHash =
nixArchiveContentHash :: IO (Digest SHA256)
nixArchiveContentHash =
Crypto.Hash.hashFinalize
<$> execStateT streamNarUpdate (Crypto.Hash.hashInit @SHA256)
@ -128,3 +119,15 @@ computeStorePathForPath storeDir name pth recursive _pathFilter _repair = do
<$> System.Nix.Nar.narReadFile
System.Nix.Nar.narEffectsIO
pth
computeStorePathForPath
:: StoreDir
-> StorePathName -- ^ Name part of the newly created `StorePath`
-> FilePath -- ^ Local `FilePath` to add
-> ContentAddressMethod -- ^ Add target directory methodly
-> PathFilter -- ^ Path filter function
-> RepairMode -- ^ Only used by local store backend
-> IO StorePath
computeStorePathForPath storeDir name pth method pathFilter repair = do
selectedHash <- digestPath pth method pathFilter repair
pure $ makeFixedOutputPath storeDir method selectedHash mempty name

View File

@ -8,7 +8,7 @@ import Test.Hspec (Spec, describe, it, shouldBe, pendingWith)
import Crypto.Hash (hash, Digest, SHA256(..))
import Data.ByteString (ByteString)
import System.Nix.StorePath (StorePath, StorePathName)
import System.Nix.Store.Types (FileIngestionMethod(..))
import System.Nix.ContentAddress (ContentAddressMethod(..))
import qualified Data.HashSet
import qualified System.Nix.StorePath
@ -56,11 +56,12 @@ spec = do
describe "makeTextPath" $ do
it "computes correct StorePath for empty refs" $
(pure
$ makeTextPath
$ makeFixedOutputPath
def
testName
ContentAddressMethod_Text
testDigest
mempty
testName
)
`shouldBe`
System.Nix.StorePath.parsePathFromText
@ -69,11 +70,12 @@ spec = do
it "computes correct StorePath for nonempty refs" $
(pure
$ makeTextPath
$ makeFixedOutputPath
def
testName
ContentAddressMethod_Text
testDigest
(Data.HashSet.fromList [ testPath, testPath2 ])
testName
)
`shouldBe`
System.Nix.StorePath.parsePathFromText
@ -85,8 +87,9 @@ spec = do
(pure
$ makeFixedOutputPath
def
FileIngestionMethod_NixArchive
ContentAddressMethod_NixArchive
testDigest
mempty
testName
)
`shouldBe`
@ -98,8 +101,9 @@ spec = do
(pure
$ makeFixedOutputPath
def
FileIngestionMethod_Flat
ContentAddressMethod_Flat
testDigest
mempty
testName
)
`shouldBe`
@ -109,11 +113,12 @@ spec = do
it "computeStorePathForText computes correct StorePath" $
(pure
$ computeStorePathForText
$ makeFixedOutputPath
def
testName
"test"
ContentAddressMethod_Text
(Crypto.Hash.hash ("test" :: ByteString) :: Digest SHA256)
(Data.HashSet.fromList [ testPath ])
testName
)
`shouldBe`
System.Nix.StorePath.parsePathFromText

View File

@ -23,7 +23,7 @@ import Control.Monad.Conc.Class (MonadConc)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Default.Class (Default(def))
import Network.Socket (Family, SockAddr(SockAddrUnix))
import System.Nix.Store.Types (FileIngestionMethod(..), RepairMode(..))
import System.Nix.Store.Types (RepairMode(..))
import System.Nix.Store.Remote.MonadStore
( runRemoteStoreT
, MonadRemoteStore(..)

View File

@ -52,7 +52,8 @@ import System.Nix.Store.Remote.Types.StoreRequest (StoreRequest(..))
import System.Nix.Store.Remote.Types.StoreText (StoreText)
import System.Nix.Store.Remote.Types.SubstituteMode (SubstituteMode)
import System.Nix.Store.Remote.Client.Core
import System.Nix.Store.Types (FileIngestionMethod(..), RepairMode(..))
import System.Nix.FileContentAddress (FileIngestionMethod(..))
import System.Nix.Store.Types (RepairMode(..))
import qualified Control.Monad.IO.Class
import qualified Data.Attoparsec.Text

View File

@ -134,7 +134,8 @@ import System.Nix.JSON ()
import System.Nix.OutputName (OutputName)
import System.Nix.Realisation (DerivationOutputError, Realisation(..), RealisationWithId(..))
import System.Nix.Signature (Signature, NarSignature)
import System.Nix.Store.Types (FileIngestionMethod(..), RepairMode(..))
import System.Nix.FileContentAddress (FileIngestionMethod(..))
import System.Nix.Store.Types (RepairMode(..))
import System.Nix.StorePath (HasStoreDir(..), InvalidNameError, InvalidPathError, StorePath, StorePathHashPart, StorePathName)
import System.Nix.StorePath.Metadata (Metadata(..), StorePathTrust(..))
import System.Nix.Store.Remote.Types

View File

@ -20,7 +20,8 @@ import System.Nix.Derivation (Derivation)
import System.Nix.DerivedPath (DerivedPath)
import System.Nix.Hash (HashAlgo)
import System.Nix.Signature (Signature)
import System.Nix.Store.Types (FileIngestionMethod, RepairMode)
import System.Nix.FileContentAddress (FileIngestionMethod)
import System.Nix.Store.Types (RepairMode)
import System.Nix.StorePath (StorePath, StorePathName, StorePathHashPart)
import System.Nix.StorePath.Metadata (Metadata)
import System.Nix.Store.Remote.Types.GC (GCOptions, GCResult, GCRoot)

View File

@ -22,6 +22,7 @@ import System.Linux.Namespaces (Namespace(..), GroupMapping(..), UserMapping(..)
import System.Nix.Hash (HashAlgo(HashAlgo_SHA256))
import System.Nix.Build (BuildMode(..))
import System.Nix.DerivedPath (DerivedPath(..))
import System.Nix.FileContentAddress (FileIngestionMethod(..))
import System.Nix.StorePath (StoreDir(..), StorePath)
import System.Nix.StorePath.Metadata (Metadata(..))
import System.Nix.Store.Remote

View File

@ -46,6 +46,7 @@ library
, System.Nix.Arbitrary.ContentAddress
, System.Nix.Arbitrary.Derivation
, System.Nix.Arbitrary.DerivedPath
, System.Nix.Arbitrary.FileContentAddress
, System.Nix.Arbitrary.Hash
, System.Nix.Arbitrary.OutputName
, System.Nix.Arbitrary.Realisation

View File

@ -10,6 +10,7 @@ import System.Nix.Arbitrary.Build ()
import System.Nix.Arbitrary.ContentAddress ()
import System.Nix.Arbitrary.Derivation ()
import System.Nix.Arbitrary.DerivedPath ()
import System.Nix.Arbitrary.FileContentAddress ()
import System.Nix.Arbitrary.Hash ()
import System.Nix.Arbitrary.OutputName ()
import System.Nix.Arbitrary.Realisation ()

View File

@ -0,0 +1,12 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.FileContentAddress where
import System.Nix.FileContentAddress
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
deriving via GenericArbitrary FileIngestionMethod
instance Arbitrary FileIngestionMethod

View File

@ -8,8 +8,5 @@ import System.Nix.Store.Types
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
deriving via GenericArbitrary FileIngestionMethod
instance Arbitrary FileIngestionMethod
deriving via GenericArbitrary RepairMode
instance Arbitrary RepairMode