mirror of
https://github.com/haskell-nix/hnix-store.git
synced 2024-11-22 19:29:48 +03:00
Clean up content address method types
This corresponds tob51e161af5
and part ofed26b186fb
This commit is contained in:
parent
12b48aeb4a
commit
43fc6d4bf2
@ -64,6 +64,7 @@ library
|
|||||||
, System.Nix.Derivation
|
, System.Nix.Derivation
|
||||||
, System.Nix.DerivedPath
|
, System.Nix.DerivedPath
|
||||||
, System.Nix.Fingerprint
|
, System.Nix.Fingerprint
|
||||||
|
, System.Nix.FileContentAddress
|
||||||
, System.Nix.Hash
|
, System.Nix.Hash
|
||||||
, System.Nix.Hash.Truncation
|
, System.Nix.Hash.Truncation
|
||||||
, System.Nix.OutputName
|
, System.Nix.OutputName
|
||||||
|
@ -1,9 +1,8 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module System.Nix.ContentAddress (
|
module System.Nix.ContentAddress (
|
||||||
ContentAddress
|
ContentAddress (..)
|
||||||
, ContentAddressMethod
|
, ContentAddressMethod (..)
|
||||||
, FileIngestionMethod
|
|
||||||
, contentAddressBuilder
|
, contentAddressBuilder
|
||||||
, contentAddressParser
|
, contentAddressParser
|
||||||
, buildContentAddress
|
, buildContentAddress
|
||||||
@ -18,7 +17,6 @@ import Data.Text (Text)
|
|||||||
import Data.Text.Lazy.Builder (Builder)
|
import Data.Text.Lazy.Builder (Builder)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import System.Nix.Hash (HashAlgo)
|
import System.Nix.Hash (HashAlgo)
|
||||||
import System.Nix.Store.Types (FileIngestionMethod(..))
|
|
||||||
|
|
||||||
import qualified Data.Attoparsec.Text
|
import qualified Data.Attoparsec.Text
|
||||||
import qualified Data.Text.Lazy
|
import qualified Data.Text.Lazy
|
||||||
@ -26,11 +24,9 @@ import qualified Data.Text.Lazy.Builder
|
|||||||
import qualified System.Nix.Hash
|
import qualified System.Nix.Hash
|
||||||
|
|
||||||
data ContentAddressMethod
|
data ContentAddressMethod
|
||||||
= FileIngestionMethod !FileIngestionMethod
|
= ContentAddressMethod_Flat
|
||||||
-- ^ The path was added to the store via makeFixedOutputPath or
|
| ContentAddressMethod_NixArchive
|
||||||
-- addToStore. It is addressed according to some hash algorithm
|
| ContentAddressMethod_Text
|
||||||
-- applied to the nar serialization via some 'NarHashMode'.
|
|
||||||
| TextIngestionMethod
|
|
||||||
-- ^ The path is a plain file added via makeTextPath or
|
-- ^ The path is a plain file added via makeTextPath or
|
||||||
-- addTextToStore. It is addressed according to a sha256sum of the
|
-- addTextToStore. It is addressed according to a sha256sum of the
|
||||||
-- file contents.
|
-- file contents.
|
||||||
@ -59,19 +55,14 @@ buildContentAddress =
|
|||||||
. contentAddressBuilder
|
. contentAddressBuilder
|
||||||
|
|
||||||
contentAddressBuilder :: ContentAddress -> Builder
|
contentAddressBuilder :: ContentAddress -> Builder
|
||||||
contentAddressBuilder (ContentAddress method digest) = case method of
|
contentAddressBuilder (ContentAddress method digest) =
|
||||||
TextIngestionMethod ->
|
(case method of
|
||||||
"text:"
|
ContentAddressMethod_Text -> "text"
|
||||||
<> System.Nix.Hash.algoDigestBuilder digest
|
ContentAddressMethod_NixArchive -> "fixed:r"
|
||||||
FileIngestionMethod r ->
|
ContentAddressMethod_Flat -> "fixed"
|
||||||
"fixed:"
|
)
|
||||||
<> fileIngestionMethodBuilder r
|
<> ":"
|
||||||
<> System.Nix.Hash.algoDigestBuilder digest
|
<> System.Nix.Hash.algoDigestBuilder digest
|
||||||
|
|
||||||
fileIngestionMethodBuilder :: FileIngestionMethod -> Builder
|
|
||||||
fileIngestionMethodBuilder = \case
|
|
||||||
FileIngestionMethod_Flat -> ""
|
|
||||||
FileIngestionMethod_NixArchive -> "r:"
|
|
||||||
|
|
||||||
-- | Parse `ContentAddressableAddress` from `ByteString`
|
-- | Parse `ContentAddressableAddress` from `ByteString`
|
||||||
parseContentAddress
|
parseContentAddress
|
||||||
@ -83,6 +74,7 @@ parseContentAddress =
|
|||||||
contentAddressParser :: Parser ContentAddress
|
contentAddressParser :: Parser ContentAddress
|
||||||
contentAddressParser = do
|
contentAddressParser = do
|
||||||
method <- parseContentAddressMethod
|
method <- parseContentAddressMethod
|
||||||
|
_ <- ":"
|
||||||
digest <- parseTypedDigest
|
digest <- parseTypedDigest
|
||||||
case digest of
|
case digest of
|
||||||
Left e -> fail e
|
Left e -> fail e
|
||||||
@ -90,10 +82,9 @@ contentAddressParser = do
|
|||||||
|
|
||||||
parseContentAddressMethod :: Parser ContentAddressMethod
|
parseContentAddressMethod :: Parser ContentAddressMethod
|
||||||
parseContentAddressMethod =
|
parseContentAddressMethod =
|
||||||
TextIngestionMethod <$ "text:"
|
(ContentAddressMethod_Text <$ "text")
|
||||||
<|> FileIngestionMethod <$ "fixed:"
|
<|> (ContentAddressMethod_NixArchive <$ "fixed:r")
|
||||||
<*> (FileIngestionMethod_NixArchive <$ "r:"
|
<|> (ContentAddressMethod_Flat <$ "fixed")
|
||||||
<|> pure FileIngestionMethod_Flat)
|
|
||||||
|
|
||||||
parseTypedDigest :: Parser (Either String (DSum HashAlgo Digest))
|
parseTypedDigest :: Parser (Either String (DSum HashAlgo Digest))
|
||||||
parseTypedDigest = System.Nix.Hash.mkNamedDigest <$> parseHashType <*> parseHash
|
parseTypedDigest = System.Nix.Hash.mkNamedDigest <$> parseHashType <*> parseHash
|
||||||
|
10
hnix-store-core/src/System/Nix/FileContentAddress.hs
Normal file
10
hnix-store-core/src/System/Nix/FileContentAddress.hs
Normal 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)
|
@ -1,17 +1,11 @@
|
|||||||
|
-- | TODO rename module
|
||||||
module System.Nix.Store.Types
|
module System.Nix.Store.Types
|
||||||
( FileIngestionMethod(..)
|
( PathFilter(..)
|
||||||
, PathFilter(..)
|
|
||||||
, RepairMode(..)
|
, RepairMode(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GHC.Generics (Generic)
|
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
|
-- | Path filtering function
|
||||||
newtype PathFilter = PathFilter
|
newtype PathFilter = PathFilter
|
||||||
{ pathFilterFunction :: FilePath -> Bool
|
{ pathFilterFunction :: FilePath -> Bool
|
||||||
|
@ -2,9 +2,7 @@
|
|||||||
|
|
||||||
module System.Nix.Store.ReadOnly
|
module System.Nix.Store.ReadOnly
|
||||||
( makeStorePath
|
( makeStorePath
|
||||||
, makeTextPath
|
|
||||||
, makeFixedOutputPath
|
, makeFixedOutputPath
|
||||||
, computeStorePathForText
|
|
||||||
, computeStorePathForPath
|
, computeStorePathForPath
|
||||||
) where
|
) where
|
||||||
|
|
||||||
@ -12,8 +10,9 @@ import Control.Monad.State (StateT, execStateT, modify)
|
|||||||
import Crypto.Hash (Context, Digest, SHA256)
|
import Crypto.Hash (Context, Digest, SHA256)
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import Data.HashSet (HashSet)
|
import Data.HashSet (HashSet)
|
||||||
|
import System.Nix.ContentAddress (ContentAddressMethod (..))
|
||||||
import System.Nix.Hash (BaseEncoding(Base16), NamedAlgo(algoName))
|
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 System.Nix.StorePath (StoreDir, StorePath, StorePathName)
|
||||||
|
|
||||||
import qualified Crypto.Hash
|
import qualified Crypto.Hash
|
||||||
@ -49,16 +48,16 @@ makeStorePath storeDir ty h nm =
|
|||||||
]
|
]
|
||||||
|
|
||||||
makeTextPath
|
makeTextPath
|
||||||
:: StoreDir
|
:: NamedAlgo _SHA256
|
||||||
-> StorePathName
|
=> StoreDir
|
||||||
-> Digest SHA256
|
-> Digest _SHA256 -- TODO enforce its it again
|
||||||
-> HashSet StorePath
|
-> HashSet StorePath
|
||||||
|
-> StorePathName
|
||||||
-> StorePath
|
-> StorePath
|
||||||
makeTextPath storeDir nm h refs = makeStorePath storeDir ty h nm
|
makeTextPath storeDir h refs nm = makeStorePath storeDir ty h nm
|
||||||
where
|
where
|
||||||
ty =
|
ty =
|
||||||
Data.ByteString.intercalate
|
Data.ByteString.intercalate ":"
|
||||||
":"
|
|
||||||
$ "text"
|
$ "text"
|
||||||
: Data.List.sort
|
: Data.List.sort
|
||||||
(System.Nix.StorePath.storePathToRawFilePath storeDir
|
(System.Nix.StorePath.storePathToRawFilePath storeDir
|
||||||
@ -68,50 +67,42 @@ makeFixedOutputPath
|
|||||||
:: forall hashAlgo
|
:: forall hashAlgo
|
||||||
. NamedAlgo hashAlgo
|
. NamedAlgo hashAlgo
|
||||||
=> StoreDir
|
=> StoreDir
|
||||||
-> FileIngestionMethod
|
-> ContentAddressMethod
|
||||||
-> Digest hashAlgo
|
-> Digest hashAlgo
|
||||||
|
-> HashSet StorePath
|
||||||
-> StorePathName
|
-> StorePathName
|
||||||
-> StorePath
|
-> StorePath
|
||||||
makeFixedOutputPath storeDir recursive h =
|
makeFixedOutputPath storeDir method h refs =
|
||||||
if recursive == FileIngestionMethod_NixArchive
|
case method of
|
||||||
&& (algoName @hashAlgo) == "sha256"
|
ContentAddressMethod_Text -> makeTextPath storeDir h refs
|
||||||
then makeStorePath storeDir "source" h
|
_ ->
|
||||||
else makeStorePath storeDir "output:out" h'
|
if method == ContentAddressMethod_NixArchive
|
||||||
|
&& (algoName @hashAlgo) == "sha256"
|
||||||
|
then makeStorePath storeDir "source" h
|
||||||
|
else makeStorePath storeDir "output:out" h'
|
||||||
where
|
where
|
||||||
h' =
|
h' =
|
||||||
Crypto.Hash.hash @ByteString @SHA256
|
Crypto.Hash.hash @ByteString @SHA256
|
||||||
$ "fixed:out:"
|
$ "fixed:out:"
|
||||||
<> Data.Text.Encoding.encodeUtf8 (algoName @hashAlgo)
|
<> 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)
|
<> Data.Text.Encoding.encodeUtf8 (System.Nix.Hash.encodeDigestWith Base16 h)
|
||||||
<> ":"
|
<> ":"
|
||||||
|
|
||||||
computeStorePathForText
|
digestPath
|
||||||
:: StoreDir
|
:: FilePath -- ^ Local `FilePath` to add
|
||||||
-> StorePathName
|
-> ContentAddressMethod -- ^ target directory method
|
||||||
-> 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
|
|
||||||
-> PathFilter -- ^ Path filter function
|
-> PathFilter -- ^ Path filter function
|
||||||
-> RepairMode -- ^ Only used by local store backend
|
-> RepairMode -- ^ Only used by local store backend
|
||||||
-> IO StorePath
|
-> IO (Digest SHA256)
|
||||||
computeStorePathForPath storeDir name pth recursive _pathFilter _repair = do
|
digestPath pth method _pathFilter _repair =
|
||||||
selectedHash <-
|
case method of
|
||||||
if recursive == FileIngestionMethod_NixArchive
|
ContentAddressMethod_Flat -> flatContentHash
|
||||||
then recursiveContentHash
|
ContentAddressMethod_NixArchive -> nixArchiveContentHash
|
||||||
else flatContentHash
|
ContentAddressMethod_Text -> flatContentHash
|
||||||
pure $ makeFixedOutputPath storeDir recursive selectedHash name
|
|
||||||
where
|
where
|
||||||
recursiveContentHash :: IO (Digest SHA256)
|
nixArchiveContentHash :: IO (Digest SHA256)
|
||||||
recursiveContentHash =
|
nixArchiveContentHash =
|
||||||
Crypto.Hash.hashFinalize
|
Crypto.Hash.hashFinalize
|
||||||
<$> execStateT streamNarUpdate (Crypto.Hash.hashInit @SHA256)
|
<$> 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.narReadFile
|
||||||
System.Nix.Nar.narEffectsIO
|
System.Nix.Nar.narEffectsIO
|
||||||
pth
|
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
|
||||||
|
@ -8,7 +8,7 @@ import Test.Hspec (Spec, describe, it, shouldBe, pendingWith)
|
|||||||
import Crypto.Hash (hash, Digest, SHA256(..))
|
import Crypto.Hash (hash, Digest, SHA256(..))
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import System.Nix.StorePath (StorePath, StorePathName)
|
import System.Nix.StorePath (StorePath, StorePathName)
|
||||||
import System.Nix.Store.Types (FileIngestionMethod(..))
|
import System.Nix.ContentAddress (ContentAddressMethod(..))
|
||||||
|
|
||||||
import qualified Data.HashSet
|
import qualified Data.HashSet
|
||||||
import qualified System.Nix.StorePath
|
import qualified System.Nix.StorePath
|
||||||
@ -56,11 +56,12 @@ spec = do
|
|||||||
describe "makeTextPath" $ do
|
describe "makeTextPath" $ do
|
||||||
it "computes correct StorePath for empty refs" $
|
it "computes correct StorePath for empty refs" $
|
||||||
(pure
|
(pure
|
||||||
$ makeTextPath
|
$ makeFixedOutputPath
|
||||||
def
|
def
|
||||||
testName
|
ContentAddressMethod_Text
|
||||||
testDigest
|
testDigest
|
||||||
mempty
|
mempty
|
||||||
|
testName
|
||||||
)
|
)
|
||||||
`shouldBe`
|
`shouldBe`
|
||||||
System.Nix.StorePath.parsePathFromText
|
System.Nix.StorePath.parsePathFromText
|
||||||
@ -69,11 +70,12 @@ spec = do
|
|||||||
|
|
||||||
it "computes correct StorePath for nonempty refs" $
|
it "computes correct StorePath for nonempty refs" $
|
||||||
(pure
|
(pure
|
||||||
$ makeTextPath
|
$ makeFixedOutputPath
|
||||||
def
|
def
|
||||||
testName
|
ContentAddressMethod_Text
|
||||||
testDigest
|
testDigest
|
||||||
(Data.HashSet.fromList [ testPath, testPath2 ])
|
(Data.HashSet.fromList [ testPath, testPath2 ])
|
||||||
|
testName
|
||||||
)
|
)
|
||||||
`shouldBe`
|
`shouldBe`
|
||||||
System.Nix.StorePath.parsePathFromText
|
System.Nix.StorePath.parsePathFromText
|
||||||
@ -85,8 +87,9 @@ spec = do
|
|||||||
(pure
|
(pure
|
||||||
$ makeFixedOutputPath
|
$ makeFixedOutputPath
|
||||||
def
|
def
|
||||||
FileIngestionMethod_NixArchive
|
ContentAddressMethod_NixArchive
|
||||||
testDigest
|
testDigest
|
||||||
|
mempty
|
||||||
testName
|
testName
|
||||||
)
|
)
|
||||||
`shouldBe`
|
`shouldBe`
|
||||||
@ -98,8 +101,9 @@ spec = do
|
|||||||
(pure
|
(pure
|
||||||
$ makeFixedOutputPath
|
$ makeFixedOutputPath
|
||||||
def
|
def
|
||||||
FileIngestionMethod_Flat
|
ContentAddressMethod_Flat
|
||||||
testDigest
|
testDigest
|
||||||
|
mempty
|
||||||
testName
|
testName
|
||||||
)
|
)
|
||||||
`shouldBe`
|
`shouldBe`
|
||||||
@ -109,11 +113,12 @@ spec = do
|
|||||||
|
|
||||||
it "computeStorePathForText computes correct StorePath" $
|
it "computeStorePathForText computes correct StorePath" $
|
||||||
(pure
|
(pure
|
||||||
$ computeStorePathForText
|
$ makeFixedOutputPath
|
||||||
def
|
def
|
||||||
testName
|
ContentAddressMethod_Text
|
||||||
"test"
|
(Crypto.Hash.hash ("test" :: ByteString) :: Digest SHA256)
|
||||||
(Data.HashSet.fromList [ testPath ])
|
(Data.HashSet.fromList [ testPath ])
|
||||||
|
testName
|
||||||
)
|
)
|
||||||
`shouldBe`
|
`shouldBe`
|
||||||
System.Nix.StorePath.parsePathFromText
|
System.Nix.StorePath.parsePathFromText
|
||||||
|
@ -23,7 +23,7 @@ import Control.Monad.Conc.Class (MonadConc)
|
|||||||
import Control.Monad.IO.Class (MonadIO, liftIO)
|
import Control.Monad.IO.Class (MonadIO, liftIO)
|
||||||
import Data.Default.Class (Default(def))
|
import Data.Default.Class (Default(def))
|
||||||
import Network.Socket (Family, SockAddr(SockAddrUnix))
|
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
|
import System.Nix.Store.Remote.MonadStore
|
||||||
( runRemoteStoreT
|
( runRemoteStoreT
|
||||||
, MonadRemoteStore(..)
|
, MonadRemoteStore(..)
|
||||||
|
@ -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.StoreText (StoreText)
|
||||||
import System.Nix.Store.Remote.Types.SubstituteMode (SubstituteMode)
|
import System.Nix.Store.Remote.Types.SubstituteMode (SubstituteMode)
|
||||||
import System.Nix.Store.Remote.Client.Core
|
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 Control.Monad.IO.Class
|
||||||
import qualified Data.Attoparsec.Text
|
import qualified Data.Attoparsec.Text
|
||||||
|
@ -134,7 +134,8 @@ import System.Nix.JSON ()
|
|||||||
import System.Nix.OutputName (OutputName)
|
import System.Nix.OutputName (OutputName)
|
||||||
import System.Nix.Realisation (DerivationOutputError, Realisation(..), RealisationWithId(..))
|
import System.Nix.Realisation (DerivationOutputError, Realisation(..), RealisationWithId(..))
|
||||||
import System.Nix.Signature (Signature, NarSignature)
|
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 (HasStoreDir(..), InvalidNameError, InvalidPathError, StorePath, StorePathHashPart, StorePathName)
|
||||||
import System.Nix.StorePath.Metadata (Metadata(..), StorePathTrust(..))
|
import System.Nix.StorePath.Metadata (Metadata(..), StorePathTrust(..))
|
||||||
import System.Nix.Store.Remote.Types
|
import System.Nix.Store.Remote.Types
|
||||||
|
@ -20,7 +20,8 @@ import System.Nix.Derivation (Derivation)
|
|||||||
import System.Nix.DerivedPath (DerivedPath)
|
import System.Nix.DerivedPath (DerivedPath)
|
||||||
import System.Nix.Hash (HashAlgo)
|
import System.Nix.Hash (HashAlgo)
|
||||||
import System.Nix.Signature (Signature)
|
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 (StorePath, StorePathName, StorePathHashPart)
|
||||||
import System.Nix.StorePath.Metadata (Metadata)
|
import System.Nix.StorePath.Metadata (Metadata)
|
||||||
import System.Nix.Store.Remote.Types.GC (GCOptions, GCResult, GCRoot)
|
import System.Nix.Store.Remote.Types.GC (GCOptions, GCResult, GCRoot)
|
||||||
|
@ -22,6 +22,7 @@ import System.Linux.Namespaces (Namespace(..), GroupMapping(..), UserMapping(..)
|
|||||||
import System.Nix.Hash (HashAlgo(HashAlgo_SHA256))
|
import System.Nix.Hash (HashAlgo(HashAlgo_SHA256))
|
||||||
import System.Nix.Build (BuildMode(..))
|
import System.Nix.Build (BuildMode(..))
|
||||||
import System.Nix.DerivedPath (DerivedPath(..))
|
import System.Nix.DerivedPath (DerivedPath(..))
|
||||||
|
import System.Nix.FileContentAddress (FileIngestionMethod(..))
|
||||||
import System.Nix.StorePath (StoreDir(..), StorePath)
|
import System.Nix.StorePath (StoreDir(..), StorePath)
|
||||||
import System.Nix.StorePath.Metadata (Metadata(..))
|
import System.Nix.StorePath.Metadata (Metadata(..))
|
||||||
import System.Nix.Store.Remote
|
import System.Nix.Store.Remote
|
||||||
|
@ -46,6 +46,7 @@ library
|
|||||||
, System.Nix.Arbitrary.ContentAddress
|
, System.Nix.Arbitrary.ContentAddress
|
||||||
, System.Nix.Arbitrary.Derivation
|
, System.Nix.Arbitrary.Derivation
|
||||||
, System.Nix.Arbitrary.DerivedPath
|
, System.Nix.Arbitrary.DerivedPath
|
||||||
|
, System.Nix.Arbitrary.FileContentAddress
|
||||||
, System.Nix.Arbitrary.Hash
|
, System.Nix.Arbitrary.Hash
|
||||||
, System.Nix.Arbitrary.OutputName
|
, System.Nix.Arbitrary.OutputName
|
||||||
, System.Nix.Arbitrary.Realisation
|
, System.Nix.Arbitrary.Realisation
|
||||||
|
@ -10,6 +10,7 @@ import System.Nix.Arbitrary.Build ()
|
|||||||
import System.Nix.Arbitrary.ContentAddress ()
|
import System.Nix.Arbitrary.ContentAddress ()
|
||||||
import System.Nix.Arbitrary.Derivation ()
|
import System.Nix.Arbitrary.Derivation ()
|
||||||
import System.Nix.Arbitrary.DerivedPath ()
|
import System.Nix.Arbitrary.DerivedPath ()
|
||||||
|
import System.Nix.Arbitrary.FileContentAddress ()
|
||||||
import System.Nix.Arbitrary.Hash ()
|
import System.Nix.Arbitrary.Hash ()
|
||||||
import System.Nix.Arbitrary.OutputName ()
|
import System.Nix.Arbitrary.OutputName ()
|
||||||
import System.Nix.Arbitrary.Realisation ()
|
import System.Nix.Arbitrary.Realisation ()
|
||||||
|
@ -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
|
@ -8,8 +8,5 @@ import System.Nix.Store.Types
|
|||||||
import Test.QuickCheck (Arbitrary(..))
|
import Test.QuickCheck (Arbitrary(..))
|
||||||
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
|
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
|
||||||
|
|
||||||
deriving via GenericArbitrary FileIngestionMethod
|
|
||||||
instance Arbitrary FileIngestionMethod
|
|
||||||
|
|
||||||
deriving via GenericArbitrary RepairMode
|
deriving via GenericArbitrary RepairMode
|
||||||
instance Arbitrary RepairMode
|
instance Arbitrary RepairMode
|
||||||
|
Loading…
Reference in New Issue
Block a user