Skip to content

Commit 6e4b72f

Browse files
committed
Add type for metadata about StorePaths.
This is a stronger-typed version of ValidPathInfo, so this fixes #43.
1 parent 61a5365 commit 6e4b72f

File tree

8 files changed

+130
-0
lines changed

8 files changed

+130
-0
lines changed

hnix-store-core/hnix-store-core.cabal

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,10 +20,13 @@ library
2020
exposed-modules: System.Nix.Base32
2121
, System.Nix.Hash
2222
, System.Nix.Internal.Hash
23+
, System.Nix.Internal.Signature
2324
, System.Nix.Internal.StorePath
2425
, System.Nix.Nar
2526
, System.Nix.ReadonlyStore
27+
, System.Nix.Signature
2628
, System.Nix.StorePath
29+
, System.Nix.StorePathMetadata
2730
, System.Nix.Util
2831
build-depends: base >=4.10 && <5
2932
, base16-bytestring
@@ -40,6 +43,8 @@ library
4043
, mtl
4144
, regex-base
4245
, regex-tdfa-text
46+
, saltine
47+
, time
4348
, text
4449
, unix
4550
, unordered-containers

hnix-store-core/src/System/Nix/Hash.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module System.Nix.Hash (
77
, HNix.HashAlgorithm(..)
88
, HNix.ValidAlgo(..)
99
, HNix.NamedAlgo(..)
10+
, HNix.SomeNamedDigest(..)
1011
, HNix.hash
1112
, HNix.hashLazy
1213

hnix-store-core/src/System/Nix/Internal/Hash.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ Description : Cryptographic hashing interface for hnix-store, on top
99
{-# LANGUAGE TypeApplications #-}
1010
{-# LANGUAGE DataKinds #-}
1111
{-# LANGUAGE OverloadedStrings #-}
12+
{-# LANGUAGE ExistentialQuantification #-}
1213

1314
module System.Nix.Internal.Hash where
1415

@@ -72,6 +73,9 @@ instance NamedAlgo 'SHA1 where
7273
instance NamedAlgo 'SHA256 where
7374
algoName = "sha256"
7475

76+
-- | A digest whose 'NamedAlgo' is not known at compile time.
77+
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a)
78+
7579
-- | Hash an entire (strict) 'BS.ByteString' as a single call.
7680
--
7781
-- For example:
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
{-|
2+
Description : Nix-relevant interfaces to NaCl signatures.
3+
-}
4+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
5+
module System.Nix.Internal.Signature where
6+
7+
import Data.ByteString (ByteString)
8+
import qualified Data.ByteString as BS
9+
import Data.Coerce (coerce)
10+
import Crypto.Saltine.Core.Sign (PublicKey)
11+
import Crypto.Saltine.Class (IsEncoding(..))
12+
import qualified Crypto.Saltine.Internal.ByteSizes as NaClSizes
13+
14+
-- | A NaCl signature.
15+
newtype Signature = Signature ByteString deriving (Eq, Ord)
16+
17+
instance IsEncoding Signature where
18+
decode s
19+
| BS.length s == NaClSizes.sign = Just (Signature s)
20+
| otherwise = Nothing
21+
encode = coerce
22+
23+
-- | A detached NaCl signature attesting to a nix archive's validity.
24+
data NarSignature = NarSignature
25+
{ -- | The public key used to sign the archive.
26+
publicKey :: PublicKey
27+
, -- | The archive's signature.
28+
sig :: Signature
29+
} deriving (Eq, Ord)

hnix-store-core/src/System/Nix/Internal/StorePath.hs

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import System.Nix.Hash
1616
( HashAlgorithm(Truncated, SHA256)
1717
, Digest
1818
, encodeBase32
19+
, SomeNamedDigest
1920
)
2021
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
2122
import Text.Regex.TDFA.Text (Regex)
@@ -68,6 +69,36 @@ type StorePathHashAlgo = 'Truncated 20 'SHA256
6869
-- | A set of 'StorePath's.
6970
type StorePathSet storeDir = HashSet (StorePath storeDir)
7071

72+
-- | An address for a content-addressable store path, i.e. one whose
73+
-- store path hash is purely a function of its contents (as opposed to
74+
-- paths that are derivation outputs, whose hashes are a function of
75+
-- the contents of the derivation file instead).
76+
--
77+
-- For backwards-compatibility reasons, the same information is
78+
-- encodable in multiple ways, depending on the method used to add the
79+
-- path to the store. These unfortunately result in separate store
80+
-- paths.
81+
data ContentAddressableAddress
82+
= -- | The path is a plain file added via makeTextPath or
83+
-- addTextToStore. It is addressed according to a sha256sum of the
84+
-- file contents.
85+
Text !(Digest 'SHA256)
86+
| -- | The path was added to the store via makeFixedOutputPath or
87+
-- addToStore. It is addressed according to some hash algorithm
88+
-- applied to the nar serialization via some 'NarHashMode'.
89+
Fixed !NarHashMode !SomeNamedDigest
90+
91+
-- | Schemes for hashing a nix archive.
92+
--
93+
-- For backwards-compatibility reasons, there are two different modes
94+
-- here, even though 'Recursive' should be able to cover both.
95+
data NarHashMode
96+
= -- | Require the nar to represent a non-executable regular file.
97+
RegularFile
98+
| -- | Hash an arbitrary nar, including a non-executable regular
99+
-- file if so desired.
100+
Recursive
101+
71102
-- | A type-level representation of the root directory of a Nix store.
72103
--
73104
-- The extra complexity of type indices requires justification.
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
{-|
2+
Description : Nix-relevant interfaces to NaCl signatures.
3+
-}
4+
module System.Nix.Signature
5+
( Signature
6+
, NarSignature(..)
7+
) where
8+
9+
import System.Nix.Internal.Signature

hnix-store-core/src/System/Nix/StorePath.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@ module System.Nix.StorePath
88
, StorePathSet
99
, StorePathHashAlgo
1010
, StoreDir
11+
, ContentAddressableAddress(..)
12+
, NarHashMode(..)
1113
, -- * Manipulating 'StorePathName'
1214
makeStorePathName
1315
, unStorePathName
Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,49 @@
1+
{-|
2+
Description : Metadata about Nix store paths.
3+
-}
4+
module System.Nix.StorePathMetadata where
5+
6+
import System.Nix.StorePath (StorePath, StorePathSet, ContentAddressableAddress)
7+
import System.Nix.Hash (SomeNamedDigest)
8+
import Data.Set (Set)
9+
import Data.Time (UTCTime)
10+
import Data.Word (Word64)
11+
import System.Nix.Signature (NarSignature)
12+
13+
-- | Metadata about a 'StorePath' in @storeDir@.
14+
data StorePathMetadata storeDir = StorePathMetadata
15+
{ -- | The path this metadata is about
16+
path :: !(StorePath storeDir)
17+
, -- | The path to the derivation file that built this path, if any
18+
-- and known.
19+
deriverPath :: !(Maybe (StorePath storeDir))
20+
, -- TODO should this be optional?
21+
-- | The hash of the nar serialization of the path.
22+
narHash :: !SomeNamedDigest
23+
, -- | The paths that this path directly references
24+
references :: !(StorePathSet storeDir)
25+
, -- | When was this path registered valid in the store?
26+
registrationTime :: !UTCTime
27+
, -- | The size of the nar serialization of the path, in bytes.
28+
narBytes :: !(Maybe Word64)
29+
, -- | How much we trust this path.
30+
trust :: !StorePathTrust
31+
, -- | A set of cryptographic attestations of this path's validity.
32+
--
33+
-- There is no guarantee from this type alone that these
34+
-- signatures are valid.
35+
sigs :: !(Set NarSignature)
36+
, -- | Whether and how this store path is content-addressable.
37+
--
38+
-- There is no guarantee from this type alone that this address
39+
-- is actually correct for this store path.
40+
contentAddressableAddress :: !(Maybe ContentAddressableAddress)
41+
}
42+
43+
-- | How much do we trust the path, based on its provenance?
44+
data StorePathTrust
45+
= -- | It was built locally and thus ultimately trusted
46+
BuiltLocally
47+
| -- | It was built elsewhere (and substituted or similar) and so
48+
-- is less trusted
49+
BuiltElsewhere

0 commit comments

Comments
 (0)